Const REG_REFRESH_HIVE = &H2 ' Unwind changes to last flush
Const REG_NOTIFY_CHANGE_NAME = &H1 ' Create or delete (child)
Const REG_NOTIFY_CHANGE_ATTRIBUTES = &H2
Const REG_NOTIFY_CHANGE_LAST_SET = &H4 ' Time stamp
Const REG_NOTIFY_CHANGE_SECURITY = &H8
Const REG_LEGAL_CHANGE_FILTER = (REG_NOTIFY_CHANGE_NAME Or REG_NOTIFY_CHANGE_ATTRIBUTES Or REG_NOTIFY_CHANGE_LAST_SET Or REG_NOTIFY_CHANGE_SECURITY)
Const REG_LEGAL_OPTION = (REG_OPTION_RESERVED Or REG_OPTION_NON_VOLATILE Or REG_OPTION_VOLATILE Or REG_OPTION_CREATE_LINK Or REG_OPTION_BACKUP_RESTORE)
' Reg Create Type Values...
Const REG_OPTION_RESERVED = 0 ' Parameter is reserved
Const REG_OPTION_NON_VOLATILE = 0 ' Key is preserved when system is rebooted
Const REG_OPTION_VOLATILE = 1 ' Key is not preserved when system is rebooted
Const REG_OPTION_CREATE_LINK = 2 ' Created key is a symbolic link
Const REG_OPTION_BACKUP_RESTORE = 4 ' open for backup or restore
' Reg Key Security Options
' Const READ_CONTROL = &H20000
Const KEY_QUERY_VALUE = &H1
Const KEY_SET_VALUE = &H2
Const KEY_CREATE_SUB_KEY = &H4
Const KEY_ENUMERATE_SUB_KEYS = &H8
Const KEY_NOTIFY = &H10
Const KEY_CREATE_LINK = &H20
Const KEY_READ = ((STANDARD_RIGHTS_READ Or KEY_QUERY_VALUE Or KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY) And (Not SYNCHRONIZE))
Const KEY_WRITE = ((STANDARD_RIGHTS_WRITE Or KEY_SET_VALUE Or KEY_CREATE_SUB_KEY) And (Not SYNCHRONIZE))
Const KEY_ALL_ACCESS = ((STANDARD_RIGHTS_ALL Or KEY_QUERY_VALUE Or KEY_SET_VALUE Or KEY_CREATE_SUB_KEY Or KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY Or KEY_CREATE_LINK) And (Not SYNCHRONIZE))
'Const STANDARD_RIGHTS_READ = (READ_CONTROL)
'Const STANDARD_RIGHTS_WRITE = (READ_CONTROL)
Const KEY_EXECUTE = ((KEY_READ) And (Not SYNCHRONIZE))
' end winnt.txt
' Debug APIs
Const EXCEPTION_DEBUG_EVENT = 1
Const CREATE_THREAD_DEBUG_EVENT = 2
Const CREATE_PROCESS_DEBUG_EVENT = 3
Const EXIT_THREAD_DEBUG_EVENT = 4
Const EXIT_PROCESS_DEBUG_EVENT = 5
Const LOAD_DLL_DEBUG_EVENT = 6
Const UNLOAD_DLL_DEBUG_EVENT = 7
Const OUTPUT_DEBUG_STRING_EVENT = 8
Const RIP_EVENT = 9
Const EXCEPTION_MAXIMUM_PARAMETERS = 15
Type EXCEPTION_RECORD
ExceptionCode As Long
ExceptionFlags As Long
pExceptionRecord As Long ' Pointer to an EXCEPTION_RECORD structure
ExceptionAddress As Long
NumberParameters As Long
ExceptionInformation(EXCEPTION_MAXIMUM_PARAMETERS) As Long
Const SECTION_ALL_ACCESS = STANDARD_RIGHTS_REQUIRED Or SECTION_QUERY Or SECTION_MAP_WRITE Or SECTION_MAP_READ Or SECTION_MAP_EXECUTE Or SECTION_EXTEND_SIZE
Const FILE_MAP_COPY = SECTION_QUERY
Const FILE_MAP_WRITE = SECTION_MAP_WRITE
Const FILE_MAP_READ = SECTION_MAP_READ
Const FILE_MAP_ALL_ACCESS = SECTION_ALL_ACCESS
' OpenFile() Flags
Const OF_READ = &H0
Const OF_WRITE = &H1
Const OF_READWRITE = &H2
Const OF_SHARE_COMPAT = &H0
Const OF_SHARE_EXCLUSIVE = &H10
Const OF_SHARE_DENY_WRITE = &H20
Const OF_SHARE_DENY_READ = &H30
Const OF_SHARE_DENY_NONE = &H40
Const OF_PARSE = &H100
Const OF_DELETE = &H200
Const OF_VERIFY = &H400
Const OF_CANCEL = &H800
Const OF_CREATE = &H1000
Const OF_PROMPT = &H2000
Const OF_EXIST = &H4000
Const OF_REOPEN = &H8000
Const OFS_MAXPATHNAME = 128
' OpenFile() Structure
Type OFSTRUCT
cBytes As Byte
fFixedDisk As Byte
nErrCode As Integer
Reserved1 As Integer
Reserved2 As Integer
szPathName(OFS_MAXPATHNAME) As Byte
End Type
Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Const PROCESSOR_INTEL_386 = 386
Const PROCESSOR_INTEL_486 = 486
Const PROCESSOR_INTEL_PENTIUM = 586
Const PROCESSOR_MIPS_R4000 = 4000
Const PROCESSOR_ALPHA_21064 = 21064
Const PROCESSOR_ARCHITECTURE_INTEL = 0
Const PROCESSOR_ARCHITECTURE_MIPS = 1
Const PROCESSOR_ARCHITECTURE_ALPHA = 2
Const PROCESSOR_ARCHITECTURE_PPC = 3
Const PROCESSOR_ARCHITECTURE_UNKNOWN = &hFFFF
Declare Function GetCurrentTime Lib "kernel32" Alias "GetTickCount" () As Long
' Flags for DrawFrameControl
Const DFC_CAPTION = 1
Const DFC_MENU = 2
Const DFC_SCROLL = 3
Const DFC_BUTTON = 4
Const DFCS_CAPTIONCLOSE = &H0
Const DFCS_CAPTIONMIN = &H1
Const DFCS_CAPTIONMAX = &H2
Const DFCS_CAPTIONRESTORE = &H3
Const DFCS_CAPTIONHELP = &H4
Const DFCS_MENUARROW = &H0
Const DFCS_MENUCHECK = &H1
Const DFCS_MENUBULLET = &H2
Const DFCS_MENUARROWRIGHT = &H4
Const DFCS_SCROLLUP = &H0
Const DFCS_SCROLLDOWN = &H1
Const DFCS_SCROLLLEFT = &H2
Const DFCS_SCROLLRIGHT = &H3
Const DFCS_SCROLLCOMBOBOX = &H5
Const DFCS_SCROLLSIZEGRIP = &H8
Const DFCS_SCROLLSIZEGRIPRIGHT = &H10
Const DFCS_BUTTONCHECK = &H0
Const DFCS_BUTTONRADIOIMAGE = &H1
Const DFCS_BUTTONRADIOMASK = &H2
Const DFCS_BUTTONRADIO = &H4
Const DFCS_BUTTON3STATE = &H8
Const DFCS_BUTTONPUSH = &H10
Const DFCS_INACTIVE = &H100
Const DFCS_PUSHED = &H200
Const DFCS_CHECKED = &H400
Const DFCS_ADJUSTRECT = &H2000
Const DFCS_FLAT = &H4000
Const DFCS_MONO = &H8000
Declare Function InterlockedIncrement Lib "kernel32" Alias "InterlockedIncrement" (lpAddend As Long) As Long
Declare Function InterlockedDecrement Lib "kernel32" Alias "InterlockedDecrement" (lpAddend As Long) As Long
Declare Function InterlockedExchange Lib "kernel32" Alias "InterlockedExchange" (Target As Long, ByVal Value As Long) As Long
' Loader Routines
Declare Function GetModuleFileName Lib "kernel32" Alias "GetModuleFileNameA" (ByVal hModule As Long, ByVal lpFileName As String, ByVal nSize As Long) As Long
Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
Declare Function CreateProcess Lib "kernel32" Alias "CreateProcessA" (ByVal lpApplicationName As String, ByVal lpCommandLine As String, lpProcessAttributes As SECURITY_ATTRIBUTES, lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, lpEnvironment As Any, ByVal lpCurrentDriectory As String, lpStartupInfo As STARTUPINFO, lpProcessInformation As PROCESS_INFORMATION) As Long
Declare Function SetProcessShutdownParameters Lib "kernel32" Alias "SetProcessShutdownParameters" (ByVal dwLevel As Long, ByVal dwFlags As Long) As Long
Declare Function GetProcessShutdownParameters Lib "kernel32" Alias "GetProcessShutdownParameters" (lpdwLevel As Long, lpdwFlags As Long) As Long
Declare Sub FatalAppExit Lib "kernel32" Alias "FatalAppExitA" (ByVal uAction As Long, ByVal lpMessageText As String)
Declare Sub GetStartupInfo Lib "kernel32" Alias "GetStartupInfoA" (lpStartupInfo As STARTUPINFO)
Declare Function GetCommandLine Lib "kernel32" Alias "GetCommandLineA" () As String
Declare Function GetEnvironmentVariable Lib "kernel32" Alias "GetEnvironmentVariableA" (ByVal lpName As String, ByVal lpBuffer As String, ByVal nSize As Long) As Long
Declare Function SetEnvironmentVariable Lib "kernel32" Alias "SetEnvironmentVariableA" (ByVal lpName As String, ByVal lpValue As String) As Long
Declare Function ExpandEnvironmentStrings Lib "kernel32" Alias "ExpandEnvironmentStringsA" (ByVal lpSrc As String, ByVal lpDst As String, ByVal nSize As Long) As Long
Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Declare Function LoadLibraryEx Lib "kernel32" Alias "LoadLibraryExA" (ByVal lpLibFileName As String, ByVal hFile As Long, ByVal dwFlags As Long) As Long
Const DONT_RESOLVE_DLL_REFERENCES = &H1
Declare Function LoadModule Lib "kernel32" Alias "LoadModule" (ByVal lpModuleName As String, lpParameterBlock As Any) As Long
Declare Function FreeLibrary Lib "kernel32" Alias "FreeLibrary" (ByVal hLibModule As Long) As Long
Declare Function WinExec Lib "kernel32" Alias "WinExec" (ByVal lpCmdLine As String, ByVal nCmdShow As Long) As Long
Declare Sub DebugBreak Lib "kernel32" Alias "DebugBreak" ()
Declare Function ContinueDebugEvent Lib "kernel32" Alias "ContinueDebugEvent" (ByVal dwProcessId As Long, ByVal dwThreadId As Long, ByVal dwContinueStatus As Long) As Long
Declare Function DebugActiveProcess Lib "kernel32" Alias "DebugActiveProcess" (ByVal dwProcessId As Long) As Long
Type CRITICAL_SECTION
dummy As Long
End Type
Declare Sub InitializeCriticalSection Lib "kernel32" Alias "InitializeCriticalSection" (lpCriticalSection As CRITICAL_SECTION)
Declare Sub EnterCriticalSection Lib "kernel32" Alias "EnterCriticalSection" (lpCriticalSection As CRITICAL_SECTION)
Declare Sub LeaveCriticalSection Lib "kernel32" Alias "LeaveCriticalSection" (lpCriticalSection As CRITICAL_SECTION)
Declare Sub DeleteCriticalSection Lib "kernel32" Alias "DeleteCriticalSection" (lpCriticalSection As CRITICAL_SECTION)
Declare Function SetEvent Lib "kernel32" Alias "SetEvent" (ByVal hEvent As Long) As Long
Declare Function ResetEvent Lib "kernel32" Alias "ResetEvent" (ByVal hEvent As Long) As Long
Declare Function PulseEvent Lib "kernel32" Alias "PulseEvent" (ByVal hEvent As Long) As Long
Declare Function ReleaseSemaphore Lib "kernel32" Alias "ReleaseSemaphore" (ByVal hSemaphore As Long, ByVal lReleaseCount As Long, lpPreviousCount As Long) As Long
Declare Function ReleaseMutex Lib "kernel32" Alias "ReleaseMutex" (ByVal hMutex As Long) As Long
Declare Function WaitForSingleObject Lib "kernel32" Alias "WaitForSingleObject" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long
Declare Function WaitForMultipleObjects Lib "kernel32" Alias "WaitForMultipleObjects" (ByVal nCount As Long, lpHandles As Long, ByVal bWaitAll As Long, ByVal dwMilliseconds As Long) As Long
Declare Sub Sleep Lib "kernel32" Alias "Sleep" (ByVal dwMilliseconds As Long)
Declare Sub OutputDebugString Lib "kernel32" Alias "OutputDebugStringA" (ByVal lpOutputString As String)
Declare Function GetVersion Lib "kernel32" Alias "GetVersion" () As Long
Declare Function OpenFile Lib "kernel32" Alias "OpenFile" (ByVal lpFileName As String, lpReOpenBuff As OFSTRUCT, ByVal wStyle As Long) As Long
' GetTempFileName() Flags
'
Const TF_FORCEDRIVE = &H80
Declare Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long
Declare Function SetHandleCount Lib "kernel32" Alias "SetHandleCount" (ByVal wNumber As Long) As Long
Declare Function GetLogicalDrives Lib "kernel32" Alias "GetLogicalDrives" () As Long
Declare Function LockFile Lib "kernel32" Alias "LockFile" (ByVal hFile As Long, ByVal dwFileOffsetLow As Long, ByVal dwFileOffsetHigh As Long, ByVal nNumberOfBytesToLockLow As Long, ByVal nNumberOfBytesToLockHigh As Long) As Long
Declare Function UnlockFile Lib "kernel32" Alias "UnlockFile" (ByVal hFile As Long, ByVal dwFileOffsetLow As Long, ByVal dwFileOffsetHigh As Long, ByVal nNumberOfBytesToUnlockLow As Long, ByVal nNumberOfBytesToUnlockHigh As Long) As Long
Declare Function LockFileEx Lib "kernel32" Alias "LockFileEx" (ByVal hFile As Long, ByVal dwFlags As Long, ByVal dwReserved As Long, ByVal nNumberOfBytesToLockLow As Long, ByVal nNumberOfBytesToLockHigh As Long, lpOverlapped As OVERLAPPED) As Long
Const LOCKFILE_FAIL_IMMEDIATELY = &H1
Const LOCKFILE_EXCLUSIVE_LOCK = &H2
Declare Function UnlockFileEx Lib "kernel32" Alias "UnlockFileEx" (ByVal hFile As Long, ByVal dwReserved As Long, ByVal nNumberOfBytesToUnlockLow As Long, ByVal nNumberOfBytesToUnlockHigh As Long, lpOverlapped As OVERLAPPED) As Long
Type BY_HANDLE_FILE_INFORMATION
dwFileAttributes As Long
ftCreationTime As FILETIME
ftLastAccessTime As FILETIME
ftLastWriteTime As FILETIME
dwVolumeSerialNumber As Long
nFileSizeHigh As Long
nFileSizeLow As Long
nNumberOfLinks As Long
nFileIndexHigh As Long
nFileIndexLow As Long
End Type
Declare Function GetFileInformationByHandle Lib "kernel32" Alias "GetFileInformationByHandle" (ByVal hFile As Long, lpFileInformation As BY_HANDLE_FILE_INFORMATION) As Long
Declare Function GetFileType Lib "kernel32" Alias "GetFileType" (ByVal hFile As Long) As Long
Declare Function GetFileSize Lib "kernel32" Alias "GetFileSize" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
Declare Function GetStdHandle Lib "kernel32" Alias "GetStdHandle" (ByVal nStdHandle As Long) As Long
Declare Function SetStdHandle Lib "kernel32" Alias "SetStdHandle" (ByVal nStdHandle As Long, ByVal nHandle As Long) As Long
Declare Function WriteFile Lib "kernel32" Alias "WriteFile" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, lpOverlapped As OVERLAPPED) As Long
Declare Function ReadFile Lib "kernel32" Alias "ReadFile" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As OVERLAPPED) As Long
Declare Function FlushFileBuffers Lib "kernel32" Alias "FlushFileBuffers" (ByVal hFile As Long) As Long
Declare Function DeviceIoControl Lib "kernel32" Alias "DeviceIoControl" (ByVal hDevice As Long, ByVal dwIoControlCode As Long, lpInBuffer As Any, ByVal nInBufferSize As Long, lpOutBuffer As Any, ByVal nOutBufferSize As Long, lpBytesReturned As Long, lpOverlapped As OVERLAPPED) As Long
Declare Function SetEndOfFile Lib "kernel32" Alias "SetEndOfFile" (ByVal hFile As Long) As Long
Declare Function SetFilePointer Lib "kernel32" Alias "SetFilePointer" (ByVal hFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
Declare Function FindClose Lib "kernel32" Alias "FindClose" (ByVal hFindFile As Long) As Long
Declare Function GetFileTime Lib "kernel32" Alias "GetFileTime" (ByVal hFile As Long, lpCreationTime As FILETIME, lpLastAccessTime As FILETIME, lpLastWriteTime As FILETIME) As Long
Declare Function SetFileTime Lib "kernel32" Alias "SetFileTime" (ByVal hFile As Long, lpCreationTime As FILETIME, lpLastAccessTime As FILETIME, lpLastWriteTime As FILETIME) As Long
Declare Function CloseHandle Lib "kernel32" Alias "CloseHandle" (ByVal hObject As Long) As Long
Declare Function DuplicateHandle Lib "kernel32" Alias "DuplicateHandle" (ByVal hSourceProcessHandle As Long, ByVal hSourceHandle As Long, ByVal hTargetProcessHandle As Long, lpTargetHandle As Long, ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwOptions As Long) As Long
Declare Function GetDriveType Lib "kernel32" Alias "GetDriveTypeA" (ByVal nDrive As String) As Long
Declare Function GlobalAlloc Lib "kernel32" Alias "GlobalAlloc" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
Declare Function GlobalFree Lib "kernel32" Alias "GlobalFree" (ByVal hMem As Long) As Long
Declare Function GlobalHandle Lib "kernel32" Alias "GlobalHandle" (wMem As Any) As Long
Declare Function GlobalLock Lib "kernel32" Alias "GlobalLock" (ByVal hMem As Long) As Long
Declare Function GlobalReAlloc Lib "kernel32" Alias "GlobalReAlloc" (ByVal hMem As Long, ByVal dwBytes As Long, ByVal wFlags As Long) As Long
Declare Function GlobalSize Lib "kernel32" Alias "GlobalSize" (ByVal hMem As Long) As Long
Declare Function GlobalUnlock Lib "kernel32" Alias "GlobalUnlock" (ByVal hMem As Long) As Long
Declare Function GlobalFlags Lib "kernel32" Alias "GlobalFlags" (ByVal hMem As Long) As Long
Declare Sub GlobalMemoryStatus Lib "kernel32" Alias "GlobalMemoryStatus" (lpBuffer As MEMORYSTATUS)
Const LNOTIFY_OUTOFMEM = 0
Const LNOTIFY_MOVE = 1
Const LNOTIFY_DISCARD = 2
Declare Function LocalAlloc Lib "kernel32" Alias "LocalAlloc" (ByVal wFlags As Long, ByVal wBytes As Long) As Long
Declare Function LocalFree Lib "kernel32" Alias "LocalFree" (ByVal hMem As Long) As Long
Declare Function LocalHandle Lib "kernel32" Alias "LocalHandle" (wMem As Any) As Long
Declare Function LocalLock Lib "kernel32" Alias "LocalLock" (ByVal hMem As Long) As Long
Declare Function LocalReAlloc Lib "kernel32" Alias "LocalReAlloc" (ByVal hMem As Long, ByVal wBytes As Long, ByVal wFlags As Long) As Long
Declare Function LocalSize Lib "kernel32" Alias "LocalSize" (ByVal hMem As Long) As Long
Declare Function LocalUnlock Lib "kernel32" Alias "LocalUnlock" (ByVal hMem As Long) As Long
Declare Function LocalFlags Lib "kernel32" Alias "LocalFlags" (ByVal hMem As Long) As Long
Type MEMORY_BASIC_INFORMATION
BaseAddress as Long
AllocationBase as Long
AllocationProtect As Long
RegionSize As Long
State As Long
Protect As Long
lType As Long
End Type
Declare Function FlushInstructionCache Lib "kernel32" Alias "FlushInstructionCache" (ByVal hProcess As Long, lpBaseAddress As Any, ByVal dwSize As Long) As Long
Declare Function VirtualAlloc Lib "kernel32" Alias "VirtualAlloc" (lpAddress As Any, ByVal dwSize As Long, ByVal flAllocationType As Long, ByVal flProtect As Long) As Long
Declare Function VirtualFree Lib "kernel32" Alias "VirtualFree" (lpAddress As Any, ByVal dwSize As Long, ByVal dwFreeType As Long) As Long
Declare Function VirtualProtect Lib "kernel32" Alias "VirtualProtect" (lpAddress As Any, ByVal dwSize As Long, ByVal flNewProtect As Long, lpflOldProtect As Long) As Long
Declare Function VirtualQuery Lib "kernel32" Alias "VirtualQuery" (lpAddress As Any, lpBuffer As MEMORY_BASIC_INFORMATION, ByVal dwLength As Long) As Long
Declare Function VirtualProtectEx Lib "kernel32" Alias "VirtualProtectEx" (ByVal hProcess As Long, lpAddress As Any, ByVal dwSize As Long, ByVal flNewProtect As Long, lpflOldProtect As Long) As Long
Declare Function VirtualQueryEx Lib "kernel32" Alias "VirtualQueryEx" (ByVal hProcess As Long, lpAddress As Any, lpBuffer As MEMORY_BASIC_INFORMATION, ByVal dwLength As Long) As Long
Declare Function HeapCreate Lib "kernel32" Alias "HeapCreate" (ByVal flOptions As Long, ByVal dwInitialSize As Long, ByVal dwMaximumSize As Long) As Long
Declare Function HeapDestroy Lib "kernel32" Alias "HeapDestroy" (ByVal hHeap As Long) As Long
Declare Function HeapAlloc Lib "kernel32" Alias "HeapAlloc" (ByVal hHeap As Long, ByVal dwFlags As Long, ByVal dwBytes As Long) As Long
Declare Function HeapReAlloc Lib "kernel32" Alias "HeapReAlloc" (ByVal hHeap As Long, ByVal dwFlags As Long, lpMem As Any, ByVal dwBytes As Long) As Long
Declare Function HeapFree Lib "kernel32" Alias "HeapFree" (ByVal hHeap As Long, ByVal dwFlags As Long, lpMem As Any) As Long
Declare Function HeapSize Lib "kernel32" Alias "HeapSize" (ByVal hHeap As Long, ByVal dwFlags As Long, lpMem As Any) As Long
Declare Function GetProcessHeap Lib "kernel32" Alias "GetProcessHeap" () As Long
Declare Function GetProcessTimes Lib "kernel32" Alias "GetProcessTimes" (ByVal hProcess As Long, lpCreationTime As FILETIME, lpExitTime As FILETIME, lpKernelTime As FILETIME, lpUserTime As FILETIME) As Long
Declare Function OpenProcess Lib "kernel32" Alias "OpenProcess" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Declare Function GetCurrentProcess Lib "kernel32" Alias "GetCurrentProcess" () As Long
Declare Function GetCurrentProcessId Lib "kernel32" Alias "GetCurrentProcessId" () As Long
Declare Sub ExitProcess Lib "kernel32" Alias "ExitProcess" (ByVal uExitCode As Long)
Declare Function TerminateProcess Lib "kernel32" Alias "TerminateProcess" (ByVal hProcess As Long, ByVal uExitCode As Long) As Long
Declare Function GetExitCodeProcess Lib "kernel32" Alias "GetExitCodeProcess" (ByVal hProcess As Long, lpExitCode As Long) As Long
Declare Function GetLastError Lib "kernel32" Alias "GetLastError" () As Long
Declare Sub SetLastError Lib "kernel32" Alias "SetLastError" (ByVal dwErrCode As Long)
Const SLE_ERROR = &H1
Const SLE_MINORERROR = &H2
Const SLE_WARNING = &H3
Declare Sub SetLastErrorEx Lib "user32" Alias "SetLastErrorEx" (ByVal dwErrCode As Long, ByVal dwType As Long)
Declare Function GetOverlappedResult Lib "kernel32" Alias "GetOverlappedResult" (ByVal hFile As Long, lpOverlapped As OVERLAPPED, lpNumberOfBytesTransferred As Long, ByVal bWait As Long) As Long
Const SEM_FAILCRITICALERRORS = &H1
Const SEM_NOGPFAULTERRORBOX = &H2
Const SEM_NOOPENFILEERRORBOX = &H8000
Declare Sub SetDebugErrorLevel Lib "user32" Alias "SetDebugErrorLevel" (ByVal dwLevel As Long)
Declare Function SetErrorMode Lib "kernel32" Alias "SetErrorMode" (ByVal wMode As Long) As Long
Declare Function ReadProcessMemory Lib "kernel32" Alias "ReadProcessMemory" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Declare Function WriteProcessMemory Lib "kernel32" Alias "WriteProcessMemory" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Declare Function GetThreadContext Lib "kernel32" Alias "GetThreadContext" (ByVal hThread As Long, lpContext As CONTEXT) As Long
Declare Function SetThreadContext Lib "kernel32" Alias "SetThreadContext" (ByVal hThread As Long, lpContext As CONTEXT) As Long
Declare Function SuspendThread Lib "kernel32" Alias "SuspendThread" (ByVal hThread As Long) As Long
Declare Function ResumeThread Lib "kernel32" Alias "ResumeThread" (ByVal hThread As Long) As Long
Declare Function FindResource Lib "kernel32" Alias "FindResourceA" (ByVal hInstance As Long, ByVal lpName As String, ByVal lpType As String) As Long
Declare Function FindResourceEx Lib "kernel32" Alias "FindResourceExA" (ByVal hModule As Long, ByVal lpType As String, ByVal lpName As String, ByVal wLanguage As Long) As Long
Declare Function BeginUpdateResource Lib "kernel32" Alias "BeginUpdateResourceA" (ByVal pFileName As String, ByVal bDeleteExistingResources As Long) As Long
Declare Function UpdateResource Lib "kernel32" Alias "UpdateResourceA" (ByVal hUpdate As Long, ByVal lpType As String, ByVal lpName As String, ByVal wLanguage As Long, lpData As Any, ByVal cbData As Long) As Long
Declare Function EndUpdateResource Lib "kernel32" Alias "EndUpdateResourceA" (ByVal hUpdate As Long, ByVal fDiscard As Long) As Long
Declare Function LoadResource Lib "kernel32" Alias "LoadResource" (ByVal hInstance As Long, ByVal hResInfo As Long) As Long
Declare Function LockResource Lib "kernel32" Alias "LockResource" (ByVal hResData As Long) As Long
Declare Function SizeofResource Lib "kernel32" Alias "SizeofResource" (ByVal hInstance As Long, ByVal hResInfo As Long) As Long
' Predefined Resource Types
Const RT_CURSOR = 1&
Const RT_BITMAP = 2&
Const RT_ICON = 3&
Const RT_MENU = 4&
Const RT_DIALOG = 5&
Const RT_STRING = 6&
Const RT_FONTDIR = 7&
Const RT_FONT = 8&
Const RT_ACCELERATOR = 9&
Const RT_RCDATA = 10&
Declare Function InitAtomTable Lib "kernel32" Alias "InitAtomTable" (ByVal nSize As Long) As Long
Declare Function GlobalAddAtom Lib "kernel32" Alias "GlobalAddAtomA" (ByVal lpString As String) As Integer
Declare Function GlobalDeleteAtom Lib "kernel32" Alias "GlobalDeleteAtom" (ByVal nAtom As Integer) As Integer
Declare Function GlobalFindAtom Lib "kernel32" Alias "GlobalFindAtomA" (ByVal lpString As String) As Integer
Declare Function GlobalGetAtomName Lib "kernel32" Alias "GlobalGetAtomNameA" (ByVal nAtom As Integer, ByVal lpBuffer As String, ByVal nSize As Long) As Long
' User Profile Routines
' NOTE: The lpKeyName argument for GetProfileString, WriteProfileString,
' GetPrivateProfileString, and WritePrivateProfileString can be either
' a string or NULL. This is why the argument is defined as "As Any".
' For example, to pass a string specify ByVal "wallpaper"
' To pass NULL specify ByVal 0&
' You can also pass NULL for the lpString argument for WriteProfileString
' and WritePrivateProfileString
Declare Function GetProfileInt Lib "kernel32" Alias "GetProfileIntA" (ByVal lpAppName As String, ByVal lpKeyName As String, ByVal nDefault As Long) As Long
Declare Function GetProfileString Lib "kernel32" Alias "GetProfileStringA" (ByVal lpAppName As String, ByVal lpKeyName As String, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long) As Long
Declare Function WriteProfileString Lib "kernel32" Alias "WriteProfileStringA" (ByVal lpszSection As String, ByVal lpszKeyName As String, ByVal lpszString As String) As Long
Declare Function GetProfileSection Lib "kernel32" Alias "GetProfileSectionA" (ByVal lpAppName As String, ByVal lpReturnedString As String, ByVal nSize As Long) As Long
Declare Function WriteProfileSection Lib "kernel32" Alias "WriteProfileSectionA" (ByVal lpAppName As String, ByVal lpString As String) As Long
Declare Function GetPrivateProfileInt Lib "kernel32" Alias "GetPrivateProfileIntA" (ByVal lpApplicationName As String, ByVal lpKeyName As String, ByVal nDefault As Long, ByVal lpFileName As String) As Long
Declare Function GetPrivateProfileString Lib "kernel32" Alias "GetPrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long
Declare Function WritePrivateProfileString Lib "kernel32" Alias "WritePrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpString As Any, ByVal lpFileName As String) As Long
Declare Function GetPrivateProfileSection Lib "kernel32" Alias "GetPrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long
Declare Function WritePrivateProfileSection Lib "kernel32" Alias "WritePrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpString As String, ByVal lpFileName As String) As Long
Declare Function GetWindowsDirectory Lib "kernel32" Alias "GetWindowsDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
Declare Function GetSystemDirectory Lib "kernel32" Alias "GetSystemDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
Declare Function GetTempPath Lib "kernel32" Alias "GetTempPathA" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long
Declare Function SetCurrentDirectory Lib "kernel32" Alias "SetCurrentDirectoryA" (ByVal lpPathName As String) As Long
Declare Function GetCurrentDirectory Lib "kernel32" Alias "GetCurrentDirectory" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long
Declare Function GetDiskFreeSpace Lib "kernel32" Alias "GetDiskFreeSpaceA" (ByVal lpRootPathName As String, lpSectorsPerCluster As Long, lpBytesPerSector As Long, lpNumberOfFreeClusters As Long, lpTotalNumberOfClusters As Long) As Long
Declare Function CreateDirectory Lib "kernel32" Alias "CreateDirectoryA" (ByVal lpPathName As String, lpSecurityAttributes As SECURITY_ATTRIBUTES) As Long
Declare Function CreateDirectoryEx Lib "kernel32" Alias "CreateDirectoryExA" (ByVal lpTemplateDirectory As String, ByVal lpNewDirectory As String, lpSecurityAttributes As SECURITY_ATTRIBUTES) As Long
Declare Function RemoveDirectory Lib "kernel32" Alias "RemoveDirectoryA" (ByVal lpPathName As String) As Long
Declare Function GetFullPathName Lib "kernel32" Alias "GetFullPathNameA" (ByVal lpFileName As String, ByVal nBufferLength As Long, ByVal lpBuffer As String, ByVal lpFilePart As String) As Long
Const DDD_RAW_TARGET_PATH = &H1
Const DDD_REMOVE_DEFINITION = &H2
Const DDD_EXACT_MATCH_ON_REMOVE = &H4
Const MAX_PATH = 260
Declare Function DefineDosDevice Lib "kernel32" Alias "DefineDosDeviceA" (ByVal dwFlags As Long, ByVal lpDeviceName As String, ByVal lpTargetPath As String) As Long
Declare Function QueryDosDevice Lib "kernel32" Alias "QueryDosDeviceA" (ByVal lpDeviceName As String, ByVal lpTargetPath As String, ByVal ucchMax As Long) As Long
Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As SECURITY_ATTRIBUTES, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Declare Function SetFileAttributes Lib "kernel32" Alias "SetFileAttributesA" (ByVal lpFileName As String, ByVal dwFileAttributes As Long) As Long
Declare Function GetFileAttributes Lib "kernel32" Alias "GetFileAttributesA" (ByVal lpFileName As String) As Long
Declare Function DeleteFile Lib "kernel32" Alias "DeleteFileA" (ByVal lpFileName As String) As Long
Declare Function FindFirstFile Lib "kernel32" Alias "FindFirstFileA" (ByVal lpFileName As String, lpFindFileData As WIN32_FIND_DATA) As Long
Declare Function FindNextFile Lib "kernel32" Alias "FindNextFileA" (ByVal hFindFile As Long, lpFindFileData As WIN32_FIND_DATA) As Long
Declare Function SearchPath Lib "kernel32" Alias "SearchPathA" (ByVal lpPath As String, ByVal lpFileName As String, ByVal lpExtension As String, ByVal nBufferLength As Long, ByVal lpBuffer As String, ByVal lpFilePart As String) As Long
Declare Function CopyFile Lib "kernel32" Alias "CopyFileA" (ByVal lpExistingFileName As String, ByVal lpNewFileName As String, ByVal bFailIfExists As Long) As Long
Declare Function MoveFile Lib "kernel32" Alias "MoveFileA" (ByVal lpExistingFileName As String, ByVal lpNewFileName As String) As Long
Declare Function MoveFileEx Lib "kernel32" Alias "MoveFileExA" (ByVal lpExistingFileName As String, ByVal lpNewFileName As String, ByVal dwFlags As Long) As Long
Const MOVEFILE_REPLACE_EXISTING = &H1
Const MOVEFILE_COPY_ALLOWED = &H2
Const MOVEFILE_DELAY_UNTIL_REBOOT = &H4
Type EVENTLOGRECORD
Length as Long ' Length of full record
Reserved as Long ' Used by the service
RecordNumber as Long ' Absolute record number
TimeGenerated as Long ' Seconds since 1-1-1970
TimeWritten as Long 'Seconds since 1-1-1970
EventID as Long
EventType as Integer
NumStrings as Integer
EventCategory as Integer
ReservedFlags as Integer ' For use with paired events (auditing)
ClosingRecordNumber as Long 'For use with paired events (auditing)
StringOffset as Long ' Offset from beginning of record
UserSidLength as Long
UserSidOffset as Long
DataLength as Long
DataOffset as Long ' Offset from beginning of record
End Type
Declare Function CreateNamedPipe Lib "kernel32" Alias "CreateNamedPipeA" (ByVal lpName As String, ByVal dwOpenMode As Long, ByVal dwPipeMode As Long, ByVal nMaxInstances As Long, ByVal nOutBufferSize As Long, ByVal nInBufferSize As Long, ByVal nDefaultTimeOut As Long, lpSecurityAttributes As SECURITY_ATTRIBUTES) As Long
Declare Function GetNamedPipeHandleState Lib "kernel32" Alias "GetNamedPipeHandleStateA" (ByVal hNamedPipe As Long, lpState As Long, lpCurInstances As Long, lpMaxCollectionCount As Long, lpCollectDataTimeout As Long, ByVal lpUserName As String, ByVal nMaxUserNameSize As Long) As Long
Declare Function CallNamedPipe Lib "kernel32" Alias "CallNamedPipeA" (ByVal lpNamedPipeName As String, lpInBuffer As Any, ByVal nInBufferSize As Long, lpOutBuffer As Any, ByVal nOutBufferSize As Long, lpBytesRead As Long, ByVal nTimeOut As Long) As Long
Declare Function WaitNamedPipe Lib "kernel32" Alias "WaitNamedPipeA" (ByVal lpNamedPipeName As String, ByVal nTimeOut As Long) As Long
Declare Function SetVolumeLabel Lib "kernel32" Alias "SetVolumeLabelA" (ByVal lpRootPathName As String, ByVal lpVolumeName As String) As Long
Declare Sub SetFileApisToOEM Lib "kernel32" Alias "SetFileApisToOEM" ()
Declare Function GetVolumeInformation Lib "kernel32" Alias "GetVolumeInformationA" (ByVal lpRootPathName As String, ByVal lpVolumeNameBuffer As String, ByVal nVolumeNameSize As Long, lpVolumeSerialNumber As Long, lpMaximumComponentLength As Long, lpFileSystemFlags As Long, ByVal lpFileSystemNameBuffer As String, ByVal nFileSystemNameSize As Long) As Long
Declare Function ClearEventLog Lib "advapi32.dll" Alias "ClearEventLogA" (ByVal hEventLog As Long, ByVal lpBackupFileName As String) As Long
Declare Function BackupEventLog Lib "advapi32.dll" Alias "BackupEventLogA" (ByVal hEventLog As Long, ByVal lpBackupFileName As String) As Long
Declare Function CloseEventLog Lib "advapi32.dll" Alias "CloseEventLog" (ByVal hEventLog As Long) As Long
Declare Function DeregisterEventSource Lib "advapi32.dll" Alias "DeregisterEventSource" (ByVal hEventLog As Long) As Long
Declare Function GetNumberOfEventLogRecords Lib "advapi32.dll" Alias "GetNumberOfEventLogRecords" (ByVal hEventLog As Long, NumberOfRecords As Long) As Long
Declare Function GetOldestEventLogRecord Lib "advapi32.dll" Alias "GetOldestEventLogRecord" (ByVal hEventLog As Long, OldestRecord As Long) As Long
Declare Function OpenEventLog Lib "advapi32.dll" Alias "OpenEventLogA" (ByVal lpUNCServerName As String, ByVal lpSourceName As String) As Long
Declare Function RegisterEventSource Lib "advapi32.dll" Alias "RegisterEventSourceA" (ByVal lpUNCServerName As String, ByVal lpSourceName As String) As Long
Declare Function OpenBackupEventLog Lib "advapi32.dll" Alias "OpenBackupEventLogA" (ByVal lpUNCServerName As String, ByVal lpFileName As String) As Long
Declare Function ReadEventLog Lib "advapi32.dll" Alias "ReadEventLogA" (ByVal hEventLog As Long, ByVal dwReadFlags As Long, ByVal dwRecordOffset As Long, lpBuffer As EVENTLOGRECORD, ByVal nNumberOfBytesToRead As Long, pnBytesRead As Long, pnMinNumberOfBytesNeeded As Long) As Long
Declare Function ReportEvent Lib "advapi32.dll" Alias "ReportEventA" (ByVal hEventLog As Long, ByVal wType As Long, ByVal wCategory As Long, ByVal dwEventID As Long, lpUserSid As Any, ByVal wNumStrings As Long, ByVal dwDataSize As Long, ByVal lpStrings As Long, lpRawData As Any) As Long
' Security APIs
Const TokenUser = 1
Const TokenGroups = 2
Const TokenPrivileges = 3
Const TokenOwner = 4
Const TokenPrimaryGroup = 5
Const TokenDefaultDacl = 6
Const TokenSource = 7
Const TokenType = 8
Const TokenImpersonationLevel = 9
Const TokenStatistics = 10
Type TOKEN_GROUPS
GroupCount As Long
Groups(ANYSIZE_ARRAY) As SID_AND_ATTRIBUTES
End Type
Declare Function DuplicateToken Lib "advapi32.dll" Alias "DuplicateToken" (ByVal ExistingTokenHandle As Long, ImpersonationLevel As Integer, DuplicateTokenHandle As Long) As Long
Declare Function GetKernelObjectSecurity Lib "advapi32.dll" Alias "GetKernelObjectSecurity" (ByVal Handle As Long, ByVal RequestedInformation As Long, pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal nLength As Long, lpnLengthNeeded As Long) As Long
Declare Function ImpersonateNamedPipeClient Lib "advapi32.dll" Alias "ImpersonateNamedPipeClient" (ByVal hNamedPipe As Long) As Long
Declare Function ImpersonateSelf Lib "advapi32.dll" Alias "ImpersonateSelf" (ImpersonationLevel As Integer) As Long
Declare Function RevertToSelf Lib "advapi32.dll" Alias "RevertToSelf" () As Long
Declare Function AccessCheck Lib "advapi32.dll" Alias "AccessCheck" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal ClientToken As Long, ByVal DesiredAccess As Long, GenericMapping As GENERIC_MAPPING, PrivilegeSet As PRIVILEGE_SET, PrivilegeSetLength As Long, GrantedAccess As Long, ByVal Status As Long) As Long
Type TOKEN_PRIVILEGES
PrivilegeCount As Long
Privileges(ANYSIZE_ARRAY) As LUID_AND_ATTRIBUTES
End Type
Declare Function OpenProcessToken Lib "advapi32.dll" Alias "OpenProcessToken" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long
Declare Function OpenThreadToken Lib "advapi32.dll" Alias "OpenThreadToken" (ByVal ThreadHandle As Long, ByVal DesiredAccess As Long, ByVal OpenAsSelf As Long, TokenHandle As Long) As Long
Declare Function GetTokenInformation Lib "advapi32.dll" Alias "GetTokenInformation" (ByVal TokenHandle As Long, TokenInformationClass As Integer, TokenInformation As Any, ByVal TokenInformationLength As Long, ReturnLength As Long) As Long
Declare Function SetTokenInformation Lib "advapi32.dll" Alias "SetTokenInformation" (ByVal TokenHandle As Long, TokenInformationClass As Integer, TokenInformation As Any, ByVal TokenInformationLength As Long) As Long
Declare Function AdjustTokenPrivileges Lib "advapi32.dll" Alias "AdjustTokenPrivileges" (ByVal TokenHandle As Long, ByVal DisableAllPrivileges As Long, NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, PreviousState As TOKEN_PRIVILEGES, ReturnLength As Long) As Long
Declare Function AdjustTokenGroups Lib "advapi32.dll" Alias "AdjustTokenGroups" (ByVal TokenHandle As Long, ByVal ResetToDefault As Long, NewState As TOKEN_GROUPS, ByVal BufferLength As Long, PreviousState As TOKEN_GROUPS, ReturnLength As Long) As Long
Declare Function PrivilegeCheck Lib "advapi32.dll" Alias "PrivilegeCheck" (ByVal ClientToken As Long, RequiredPrivileges As PRIVILEGE_SET, ByVal pfResult As Long) As Long
Declare Function AccessCheckAndAuditAlarm Lib "advapi32.dll" Alias "AccessCheckAndAuditAlarmA" (ByVal SubsystemName As String, HandleId As Any, ByVal ObjectTypeName As String, ByVal ObjectName As String, SecurityDescriptor As SECURITY_DESCRIPTOR, ByVal DesiredAccess As Long, GenericMapping As GENERIC_MAPPING, ByVal ObjectCreation As Long, GrantedAccess As Long, ByVal AccessStatus As Long, ByVal pfGenerateOnClose As Long) As Long
Declare Function ObjectOpenAuditAlarm Lib "kernel32" Alias "ObjectOpenAuditAlarmA" (ByVal SubsystemName As String, HandleId As Any, ByVal ObjectTypeName As String, ByVal ObjectName As String, pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal ClientToken As Long, ByVal DesiredAccess As Long, ByVal GrantedAccess As Long, Privileges As PRIVILEGE_SET, ByVal ObjectCreation As Long, ByVal AccessGranted As Long, ByVal GenerateOnClose As Long) As Long
Declare Function ObjectPrivilegeAuditAlarm Lib "advapi32.dll" Alias "ObjectPrivilegeAuditAlarmA" (ByVal SubsystemName As String, HandleId As Any, ByVal ClientToken As Long, ByVal DesiredAccess As Long, Privileges As PRIVILEGE_SET, ByVal AccessGranted As Long) As Long
Declare Function ObjectCloseAuditAlarm Lib "advapi32.dll" Alias "ObjectCloseAuditAlarmA" (ByVal SubsystemName As String, HandleId As Any, ByVal GenerateOnClose As Long) As Long
Declare Function PrivilegedServiceAuditAlarm Lib "advapi32.dll" Alias "PrivilegedServiceAuditAlarmA" (ByVal SubsystemName As String, ByVal ServiceName As String, ByVal ClientToken As Long, Privileges As PRIVILEGE_SET, ByVal AccessGranted As Long) As Long
Declare Function IsValidSid Lib "advapi32.dll" Alias "IsValidSid" (pSid As Any) As Long
Declare Function EqualSid Lib "advapi32.dll" Alias "EqualSid" (pSid1 As Any, pSid2 As Any) As Long
Declare Function EqualPrefixSid Lib "advapi32.dll" Alias "EqualPrefixSid" (pSid1 As Any, pSid2 As Any) As Long
Declare Function GetSidLengthRequired Lib "advapi32.dll" Alias "GetSidLengthRequired" (ByVal nSubAuthorityCount As Byte) As Long
Declare Function AllocateAndInitializeSid Lib "advapi32.dll" Alias "AllocateAndInitializeSid" (pIdentifierAuthority As SID_IDENTIFIER_AUTHORITY, ByVal nSubAuthorityCount As Byte, ByVal nSubAuthority0 As Long, ByVal nSubAuthority1 As Long, ByVal nSubAuthority2 As Long, ByVal nSubAuthority3 As Long, ByVal nSubAuthority4 As Long, ByVal nSubAuthority5 As Long, ByVal nSubAuthority6 As Long, ByVal nSubAuthority7 As Long, lpPSid As Long) As Long
Declare Sub FreeSid Lib "advapi32.dll" Alias "FreeSid" (pSid As Any)
Declare Function InitializeSid Lib "advapi32.dll" Alias "InitializeSid" (Sid As Any, pIdentifierAuthority As SID_IDENTIFIER_AUTHORITY, ByVal nSubAuthorityCount As Byte) As Long
Declare Function GetSidIdentifierAuthority Lib "advapi32.dll" Alias "GetSidIdentifierAuthority" (pSid As Any) As SID_IDENTIFIER_AUTHORITY
Declare Function GetSidSubAuthority Lib "advapi32.dll" Alias "GetSidSubAuthority" (pSid As Any, ByVal nSubAuthority As Long) As Long
Declare Function GetSidSubAuthorityCount Lib "advapi32.dll" Alias "GetSidSubAuthorityCount" (pSid As Any) As Byte
Declare Function GetLengthSid Lib "advapi32.dll" Alias "GetLengthSid" (pSid As Any) As Long
Declare Function CopySid Lib "advapi32.dll" Alias "CopySid" (ByVal nDestinationSidLength As Long, pDestinationSid As Any, pSourceSid As Any) As Long
Declare Function AreAllAccessesGranted Lib "advapi32.dll" Alias "AreAllAccessesGranted" (ByVal GrantedAccess As Long, ByVal DesiredAccess As Long) As Long
Declare Function AreAnyAccessesGranted Lib "advapi32.dll" Alias "AreAnyAccessesGranted" (ByVal GrantedAccess As Long, ByVal DesiredAccess As Long) As Long
Declare Sub MapGenericMask Lib "advapi32.dll" Alias "MapGenericMask" (AccessMask As Long, GenericMapping As GENERIC_MAPPING)
Declare Function IsValidAcl Lib "advapi32.dll" Alias "IsValidAcl" (pAcl As ACL) As Long
Declare Function InitializeAcl Lib "advapi32.dll" Alias "InitializeAcl" (pAcl As ACL, ByVal nAclLength As Long, ByVal dwAclRevision As Long) As Long
Declare Function GetAclInformation Lib "advapi32.dll" Alias "GetAclInformation" (pAcl As ACL, pAclInformation As Any, ByVal nAclInformationLength As Long, ByVal dwAclInformationClass As Integer) As Long
Declare Function SetAclInformation Lib "advapi32.dll" Alias "SetAclInformation" (pAcl As ACL, pAclInformation As Any, ByVal nAclInformationLength As Long, ByVal dwAclInformationClass As Integer) As Long
Declare Function AddAce Lib "advapi32.dll" Alias "AddAce" (pAcl As ACL, ByVal dwAceRevision As Long, ByVal dwStartingAceIndex As Long, pAceList As Any, ByVal nAceListLength As Long) As Long
Declare Function DeleteAce Lib "advapi32.dll" Alias "DeleteAce" (pAcl As ACL, ByVal dwAceIndex As Long) As Long
Declare Function GetAce Lib "advapi32.dll" Alias "GetAce" (pAcl As ACL, ByVal dwAceIndex As Long, pAce As Any) As Long
Declare Function AddAccessAllowedAce Lib "advapi32.dll" Alias "AddAccessAllowedAce" (pAcl As ACL, ByVal dwAceRevision As Long, ByVal AccessMask As Long, pSid As Any) As Long
Declare Function AddAccessDeniedAce Lib "advapi32.dll" Alias "AddAccessDeniedAce" (pAcl As ACL, ByVal dwAceRevision As Long, ByVal AccessMask As Long, pSid As Any) As Long
Declare Function AddAuditAccessAce Lib "advapi32.dll" Alias "AddAuditAccessAce" (pAcl As ACL, ByVal dwAceRevision As Long, ByVal dwAccessMask As Long, pSid As Any, ByVal bAuditSuccess As Long, ByVal bAuditFailure As Long) As Long
Declare Function FindFirstFreeAce Lib "advapi32.dll" Alias "FindFirstFreeAce" (pAcl As ACL, pAce As Long) As Long
Declare Function InitializeSecurityDescriptor Lib "advapi32.dll" Alias "InitializeSecurityDescriptor" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal dwRevision As Long) As Long
Declare Function IsValidSecurityDescriptor Lib "advapi32.dll" Alias "IsValidSecurityDescriptor" (pSecurityDescriptor As SECURITY_DESCRIPTOR) As Long
Declare Function GetSecurityDescriptorLength Lib "advapi32.dll" Alias "GetSecurityDescriptorLength" (pSecurityDescriptor As SECURITY_DESCRIPTOR) As Long
Declare Function GetSecurityDescriptorControl Lib "advapi32.dll" Alias "GetSecurityDescriptorControl" (pSecurityDescriptor As SECURITY_DESCRIPTOR, pControl As Integer, lpdwRevision As Long) As Long
Declare Function SetSecurityDescriptorDacl Lib "advapi32.dll" Alias "SetSecurityDescriptorDacl" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal bDaclPresent As Long, pDacl As ACL, ByVal bDaclDefaulted As Long) As Long
Declare Function GetSecurityDescriptorDacl Lib "advapi32.dll" Alias "GetSecurityDescriptorDacl" (pSecurityDescriptor As SECURITY_DESCRIPTOR, lpbDaclPresent As Long, pDacl As ACL, lpbDaclDefaulted As Long) As Long
Declare Function SetSecurityDescriptorSacl Lib "advapi32.dll" Alias "SetSecurityDescriptorSacl" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal bSaclPresent As Long, pSacl As ACL, ByVal bSaclDefaulted As Long) As Long
Declare Function GetSecurityDescriptorSacl Lib "advapi32.dll" Alias "GetSecurityDescriptorSacl" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal lpbSaclPresent As Long, pSacl As ACL, ByVal lpbSaclDefaulted As Long) As Long
Declare Function SetSecurityDescriptorOwner Lib "advapi32.dll" Alias "SetSecurityDescriptorOwner" (pSecurityDescriptor As SECURITY_DESCRIPTOR, pOwner As Any, ByVal bOwnerDefaulted As Long) As Long
Declare Function GetSecurityDescriptorOwner Lib "advapi32.dll" Alias "GetSecurityDescriptorOwner" (pSecurityDescriptor As SECURITY_DESCRIPTOR, pOwner As Any, ByVal lpbOwnerDefaulted As Long) As Long
Declare Function SetSecurityDescriptorGroup Lib "advapi32.dll" Alias "SetSecurityDescriptorGroup" (pSecurityDescriptor As SECURITY_DESCRIPTOR, pGroup As Any, ByVal bGroupDefaulted As Long) As Long
Declare Function GetSecurityDescriptorGroup Lib "advapi32.dll" Alias "GetSecurityDescriptorGroup" (pSecurityDescriptor As SECURITY_DESCRIPTOR, pGroup As Any, ByVal lpbGroupDefaulted As Long) As Long
Declare Function CreatePrivateObjectSecurity Lib "advapi32.dll" Alias "CreatePrivateObjectSecurity" (ParentDescriptor As SECURITY_DESCRIPTOR, CreatorDescriptor As SECURITY_DESCRIPTOR, NewDescriptor As SECURITY_DESCRIPTOR, ByVal IsDirectoryObject As Long, ByVal Token As Long, GenericMapping As GENERIC_MAPPING) As Long
Declare Function SetPrivateObjectSecurity Lib "advapi32.dll" Alias "SetPrivateObjectSecurity" (ByVal SecurityInformation As Long, ModificationDescriptor As SECURITY_DESCRIPTOR, ObjectsSecurityDescriptor As SECURITY_DESCRIPTOR, GenericMapping As GENERIC_MAPPING, ByVal Token As Long) As Long
Declare Function GetPrivateObjectSecurity Lib "advapi32.dll" Alias "GetPrivateObjectSecurity" (ObjectDescriptor As SECURITY_DESCRIPTOR, ByVal SecurityInformation As Long, ResultantDescriptor As SECURITY_DESCRIPTOR, ByVal DescriptorLength As Long, ReturnLength As Long) As Long
Declare Function DestroyPrivateObjectSecurity Lib "advapi32.dll" Alias "DestroyPrivateObjectSecurity" (ObjectDescriptor As SECURITY_DESCRIPTOR) As Long
Declare Function MakeSelfRelativeSD Lib "advapi32.dll" Alias "MakeSelfRelativeSD" (pAbsoluteSecurityDescriptor As SECURITY_DESCRIPTOR, pSelfRelativeSecurityDescriptor As SECURITY_DESCRIPTOR, lpdwBufferLength As Long) As Long
Declare Function MakeAbsoluteSD Lib "advapi32.dll" Alias "MakeAbsoluteSD" (pSelfRelativeSecurityDescriptor As SECURITY_DESCRIPTOR, pAbsoluteSecurityDescriptor As SECURITY_DESCRIPTOR, lpdwAbsoluteSecurityDescriptorSize As Long, pDacl As ACL, lpdwDaclSize As Long, pSacl As ACL, lpdwSaclSize As Long, pOwner As Any, lpdwOwnerSize As Long, pPrimaryGroup As Any, lpdwPrimaryGroupSize As Long) As Long
Declare Function SetFileSecurity Lib "advapi32.dll" Alias "SetFileSecurityA" (ByVal lpFileName As String, ByVal SecurityInformation As Long, pSecurityDescriptor As SECURITY_DESCRIPTOR) As Long
Declare Function GetFileSecurity Lib "advapi32.dll" Alias "GetFileSecurityA" (ByVal lpFileName As String, ByVal RequestedInformation As Long, pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal nLength As Long, lpnLengthNeeded As Long) As Long
Declare Function SetKernelObjectSecurity Lib "advapi32.dll" Alias "SetKernelObjectSecurity" (ByVal Handle As Long, ByVal SecurityInformation As Long, SecurityDescriptor As SECURITY_DESCRIPTOR) As Long
Declare Function FindFirstChangeNotification Lib "kernel32" Alias "FindFirstChangeNotificationA" (ByVal lpPathName As String, ByVal bWatchSubtree As Long, ByVal dwNotifyFilter As Long) As Long
Declare Function FindNextChangeNotification Lib "kernel32" Alias "FindNextChangeNotification" (ByVal hChangeHandle As Long) As Long
Declare Function FindCloseChangeNotification Lib "kernel32" Alias "FindCloseChangeNotification" (ByVal hChangeHandle As Long) As Long
Declare Function VirtualLock Lib "kernel32" Alias "VirtualLock" (lpAddress As Any, ByVal dwSize As Long) As Long
Declare Function VirtualUnlock Lib "kernel32" Alias "VirtualUnlock" (lpAddress As Any, ByVal dwSize As Long) As Long
Declare Function MapViewOfFileEx Lib "kernel32" Alias "MapViewOfFileEx" (ByVal hFileMappingObject As Long, ByVal dwDesiredAccess As Long, ByVal dwFileOffsetHigh As Long, ByVal dwFileOffsetLow As Long, ByVal dwNumberOfBytesToMap As Long, lpBaseAddress As Any) As Long
Declare Function SetPriorityClass Lib "kernel32" Alias "SetPriorityClass" (ByVal hProcess As Long, ByVal dwPriorityClass As Long) As Long
Declare Function GetPriorityClass Lib "kernel32" Alias "GetPriorityClass" (ByVal hProcess As Long) As Long
Type CONTEXT
FltF0 As Double
FltF1 As Double
FltF2 As Double
FltF3 As Double
FltF4 As Double
FltF5 As Double
FltF6 As Double
FltF7 As Double
FltF8 As Double
FltF9 As Double
FltF10 As Double
FltF11 As Double
FltF12 As Double
FltF13 As Double
FltF14 As Double
FltF15 As Double
FltF16 As Double
FltF17 As Double
FltF18 As Double
FltF19 As Double
FltF20 As Double
FltF21 As Double
FltF22 As Double
FltF23 As Double
FltF24 As Double
FltF25 As Double
FltF26 As Double
FltF27 As Double
FltF28 As Double
FltF29 As Double
FltF30 As Double
FltF31 As Double
IntV0 As Double
IntT0 As Double
IntT1 As Double
IntT2 As Double
IntT3 As Double
IntT4 As Double
IntT5 As Double
IntT6 As Double
IntT7 As Double
IntS0 As Double
IntS1 As Double
IntS2 As Double
IntS3 As Double
IntS4 As Double
IntS5 As Double
IntFp As Double
IntA0 As Double
IntA1 As Double
IntA2 As Double
IntA3 As Double
IntA4 As Double
IntA5 As Double
IntT8 As Double
IntT9 As Double
IntT10 As Double
IntT11 As Double
IntRa As Double
IntT12 As Double
IntAt As Double
IntGp As Double
IntSp As Double
IntZero As Double
Fpcr As Double
SoftFpcr As Double
Fir As Double
Psr As Long
ContextFlags As Long
Fill(4) As Long
End Type
Type EXCEPTION_POINTERS
pExceptionRecord As EXCEPTION_RECORD
ContextRecord As CONTEXT
End Type
Type LDT_BYTES ' Defined for use in LDT_ENTRY Type
BaseMid As Byte
Flags1 As Byte
Flags2 As Byte
BaseHi As Byte
End Type
Type LDT_ENTRY
LimitLow As Integer
BaseLow As Integer
HighWord As Long ' Can use LDT_BYTES Type
End Type
Declare Sub FatalExit Lib "kernel32" Alias "FatalExit" (ByVal code As Long)
Declare Function GetEnvironmentStrings Lib "kernel32" Alias "GetEnvironmentStringsA" () As String
Declare Sub RaiseException Lib "kernel32" Alias "RaiseException" (ByVal dwExceptionCode As Long, ByVal dwExceptionFlags As Long, ByVal nNumberOfArguments As Long, lpArguments As Long)
Declare Function UnhandledExceptionFilter Lib "kernel32" Alias "UnhandledExceptionFilter" (ExceptionInfo As EXCEPTION_POINTERS) As Long
Declare Function CreateThread Lib "kernel32" Alias "CreateThread" (lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal dwStackSize As Long, lpStartAddress As Long, lpParameter As Any, ByVal dwCreationFlags As Long, lpThreadId As Long) As Long
Declare Function CreateRemoteThread Lib "kernel32" Alias "CreateRemoteThread" (ByVal hProcess As Long, lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal dwStackSize As Long, lpStartAddress As Long, lpParameter As Any, ByVal dwCreationFlags As Long, lpThreadId As Long) As Long
Declare Function GetCurrentThread Lib "kernel32" Alias "GetCurrentThread" () As Long
Declare Function GetCurrentThreadId Lib "kernel32" Alias "GetCurrentThreadId" () As Long
Declare Function SetThreadPriority Lib "kernel32" Alias "SetThreadPriority" (ByVal hThread As Long, ByVal nPriority As Long) As Long
Declare Function GetThreadPriority Lib "kernel32" Alias "GetThreadPriority" (ByVal hThread As Long) As Long
Declare Function GetThreadTimes Lib "kernel32" Alias "GetThreadTimes" (ByVal hThread As Long, lpCreationTime As FILETIME, lpExitTime As FILETIME, lpKernelTime As FILETIME, lpUserTime As FILETIME) As Long
Declare Sub ExitThread Lib "kernel32" Alias "ExitThread" (ByVal dwExitCode As Long)
Declare Function TerminateThread Lib "kernel32" Alias "TerminateThread" (ByVal hThread As Long, ByVal dwExitCode As Long) As Long
Declare Function GetExitCodeThread Lib "kernel32" Alias "GetExitCodeThread" (ByVal hThread As Long, lpExitCode As Long) As Long
Declare Function GetThreadSelectorEntry Lib "kernel32" Alias "GetThreadSelectorEntry" (ByVal hThread As Long, ByVal dwSelector As Long, lpSelectorEntry As LDT_ENTRY) As Long
' COMM declarations
Declare Function SetCommState Lib "kernel32" Alias "SetCommState" (ByVal hCommDev As Long, lpDCB As DCB) As Long
Declare Function SetCommTimeouts Lib "kernel32" Alias "SetCommTimeouts" (ByVal hFile As Long, lpCommTimeouts As COMMTIMEOUTS) As Long
Declare Function GetCommState Lib "kernel32" Alias "GetCommState" (ByVal nCid As Long, lpDCB As DCB) As Long
Declare Function GetCommTimeouts Lib "kernel32" Alias "GetCommTimeouts" (ByVal hFile As Long, lpCommTimeouts As COMMTIMEOUTS) As Long
Declare Function PurgeComm Lib "kernel32" Alias "PurgeComm" (ByVal hFile As Long, ByVal dwFlags As Long) As Long
Declare Function BuildCommDCB Lib "kernel32" Alias "BuildCommDCBA" (ByVal lpDef As String, lpDCB As DCB) As Long
Declare Function BuildCommDCBAndTimeouts Lib "kernel32" Alias "BuildCommDCBAndTimeoutsA" (ByVal lpDef As String, lpDCB As DCB, lpCommTimeouts As COMMTIMEOUTS) As Long
Declare Function TransmitCommChar Lib "kernel32" Alias "TransmitCommChar" (ByVal nCid As Long, ByVal cChar As Byte) As Long
Declare Function SetCommBreak Lib "kernel32" Alias "SetCommBreak" (ByVal nCid As Long) As Long
Declare Function SetCommMask Lib "kernel32" Alias "SetCommMask" (ByVal hFile As Long, ByVal dwEvtMask As Long) As Long
Declare Function ClearCommBreak Lib "kernel32" Alias "ClearCommBreak" (ByVal nCid As Long) As Long
Declare Function ClearCommError Lib "kernel32" Alias "ClearCommError" (ByVal hFile As Long, lpErrors As Long, lpStat As COMSTAT) As Long
Declare Function SetupComm Lib "kernel32" Alias "SetupComm" (ByVal hFile As Long, ByVal dwInQueue As Long, ByVal dwOutQueue As Long) As Long
Declare Function EscapeCommFunction Lib "kernel32" Alias "EscapeCommFunction" (ByVal nCid As Long, ByVal nFunc As Long) As Long
Declare Function GetCommMask Lib "kernel32" Alias "GetCommMask" (ByVal hFile As Long, lpEvtMask As Long) As Long
Declare Function GetCommProperties Lib "kernel32" Alias "GetCommProperties" (ByVal hFile As Long, lpCommProp As COMMPROP) As Long
Declare Function GetCommModemStatus Lib "kernel32" Alias "GetCommModemStatus" (ByVal hFile As Long, lpModemStat As Long) As Long
Declare Function WaitCommEvent Lib "kernel32" Alias "WaitCommEvent" (ByVal hFile As Long, lpEvtMask As Long, lpOverlapped As OVERLAPPED) As Long
Declare Function SetTapePosition Lib "kernel32" Alias "SetTapePosition" (ByVal hDevice As Long, ByVal dwPositionMethod As Long, ByVal dwPartition As Long, ByVal dwOffsetLow As Long, ByVal dwOffsetHigh As Long, ByVal bimmediate As Long) As Long
Declare Function GetTapePosition Lib "kernel32" Alias "GetTapePosition" (ByVal hDevice As Long, ByVal dwPositionType As Long, lpdwPartition As Long, lpdwOffsetLow As Long, lpdwOffsetHigh As Long) As Long
Declare Function PrepareTape Lib "kernel32" Alias "PrepareTape" (ByVal hDevice As Long, ByVal dwOperation As Long, ByVal bimmediate As Long) As Long
Declare Function EraseTape Lib "kernel32" Alias "EraseTape" (ByVal hDevice As Long, ByVal dwEraseType As Long, ByVal bimmediate As Long) As Long
Declare Function CreateTapePartition Lib "kernel32" Alias "CreateTapePartition" (ByVal hDevice As Long, ByVal dwPartitionMethod As Long, ByVal dwCount As Long, ByVal dwSize As Long) As Long
Declare Function WriteTapemark Lib "kernel32" Alias "WriteTapemark" (ByVal hDevice As Long, ByVal dwTapemarkType As Long, ByVal dwTapemarkCount As Long, ByVal bimmediate As Long) As Long
Declare Function GetTapeStatus Lib "kernel32" Alias "GetTapeStatus" (ByVal hDevice As Long) As Long
Declare Function GetTapeParameters Lib "kernel32" Alias "GetTapeParameters" (ByVal hDevice As Long, ByVal dwOperation As Long, lpdwSize As Long, lpTapeInformation As Any) As Long
Const GET_TAPE_MEDIA_INFORMATION = 0
Const GET_TAPE_DRIVE_INFORMATION = 1
Declare Function SetTapeParameters Lib "kernel32" Alias "SetTapeParameters" (ByVal hDevice As Long, ByVal dwOperation As Long, lpTapeInformation As Any) As Long
Const SET_TAPE_MEDIA_INFORMATION = 0
Const SET_TAPE_DRIVE_INFORMATION = 1
Declare Function Beep Lib "kernel32" Alias "Beep" (ByVal dwFreq As Long, ByVal dwDuration As Long) As Long
Declare Function MulDiv Lib "kernel32" Alias "MulDiv" (ByVal nNumber As Long, ByVal nNumerator As Long, ByVal nDenominator As Long) As Long
Declare Sub GetSystemTime Lib "kernel32" Alias "GetSystemTime" (lpSystemTime As SYSTEMTIME)
Declare Function SetSystemTime Lib "kernel32" Alias "SetSystemTime" (lpSystemTime As SYSTEMTIME) As Long
Declare Sub GetLocalTime Lib "kernel32" Alias "GetLocalTime" (lpSystemTime As SYSTEMTIME)
Declare Function SetLocalTime Lib "kernel32" Alias "SetLocalTime" (lpSystemTime As SYSTEMTIME) As Long
Declare Sub GetSystemInfo Lib "kernel32" Alias "GetSystemInfo" (lpSystemInfo As SYSTEM_INFO)
Type TIME_ZONE_INFORMATION
Bias As Long
StandardName(32) As Integer
StandardDate As SYSTEMTIME
StandardBias As Long
DaylightName(32) As Integer
DaylightDate As SYSTEMTIME
DaylightBias As Long
End Type
Declare Function GetTimeZoneInformation Lib "kernel32" Alias "GetTimeZoneInformation" (lpTimeZoneInformation As TIME_ZONE_INFORMATION) As Long
Declare Function SetTimeZoneInformation Lib "kernel32" Alias "SetTimeZoneInformation" (lpTimeZoneInformation As TIME_ZONE_INFORMATION) As Long
' Routines to convert back and forth
' between system time and file time
Declare Function SystemTimeToFileTime Lib "kernel32" Alias "SystemTimeToFileTime" (lpSystemTime As SYSTEMTIME, lpFileTime As FILETIME) As Long
Declare Function FileTimeToLocalFileTime Lib "kernel32" Alias "FileTimeToLocalFileTime" (lpFileTime As FILETIME, lpLocalFileTime As FILETIME) As Long
Declare Function LocalFileTimeToFileTime Lib "kernel32" Alias "LocalFileTimeToFileTime" (lpLocalFileTime As FILETIME, lpFileTime As FILETIME) As Long
Declare Function FileTimeToSystemTime Lib "kernel32" Alias "FileTimeToSystemTime" (lpFileTime As FILETIME, lpSystemTime As SYSTEMTIME) As Long
Declare Function CompareFileTime Lib "kernel32" Alias "CompareFileTime" (lpFileTime1 As FILETIME, lpFileTime2 As FILETIME) As Long
Declare Function FileTimeToDosDateTime Lib "kernel32" Alias "FileTimeToDosDateTime" (lpFileTime As FILETIME, ByVal lpFatDate As Long, ByVal lpFatTime As Long) As Long
Declare Function DosDateTimeToFileTime Lib "kernel32" Alias "DosDateTimeToFileTime" (ByVal wFatDate As Long, ByVal wFatTime As Long, lpFileTime As FILETIME) As Long
Declare Function GetTickCount Lib "kernel32" Alias "GetTickCount" () As Long
Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" (ByVal dwFlags As Long, lpSource As Any, ByVal dwMessageId As Long, ByVal dwLanguageId As Long, ByVal lpBuffer As String, ByVal nSize As Long, Arguments As Long) As Long
Const FORMAT_MESSAGE_ALLOCATE_BUFFER = &H100
Const FORMAT_MESSAGE_IGNORE_INSERTS = &H200
Const FORMAT_MESSAGE_FROM_STRING = &H400
Const FORMAT_MESSAGE_FROM_HMODULE = &H800
Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
Const FORMAT_MESSAGE_ARGUMENT_ARRAY = &H2000
Const FORMAT_MESSAGE_MAX_WIDTH_MASK = &HFF
Declare Function CreatePipe Lib "kernel32" Alias "CreatePipe" (phReadPipe As Long, phWritePipe As Long, lpPipeAttributes As SECURITY_ATTRIBUTES, ByVal nSize As Long) As Long
Declare Function ConnectNamedPipe Lib "kernel32" Alias "ConnectNamedPipe" (ByVal hNamedPipe As Long, lpOverlapped As OVERLAPPED) As Long
Declare Function DisconnectNamedPipe Lib "kernel32" Alias "DisconnectNamedPipe" (ByVal hNamedPipe As Long) As Long
Declare Function SetNamedPipeHandleState Lib "kernel32" Alias "SetNamedPipeHandleState" (ByVal hNamedPipe As Long, lpMode As Long, lpMaxCollectionCount As Long, lpCollectDataTimeout As Long) As Long
Declare Function GetNamedPipeInfo Lib "kernel32" Alias "GetNamedPipeInfo" (ByVal hNamedPipe As Long, lpFlags As Long, lpOutBufferSize As Long, lpInBufferSize As Long, lpMaxInstances As Long) As Long
Declare Function PeekNamedPipe Lib "kernel32" Alias "PeekNamedPipe" (ByVal hNamedPipe As Long, lpBuffer As Any, ByVal nBufferSize As Long, lpBytesRead As Long, lpTotalBytesAvail As Long, lpBytesLeftThisMessage As Long) As Long
Declare Function TransactNamedPipe Lib "kernel32" Alias "TransactNamedPipe" (ByVal hNamedPipe As Long, lpInBuffer As Any, ByVal nInBufferSize As Long, lpOutBuffer As Any, ByVal nOutBufferSize As Long, lpBytesRead As Long, lpOverlapped As OVERLAPPED) As Long
Declare Function CreateMailslot Lib "kernel32" Alias "CreateMailslotA" (ByVal lpName As String, ByVal nMaxMessageSize As Long, ByVal lReadTimeout As Long, lpSecurityAttributes As SECURITY_ATTRIBUTES) As Long
Declare Function GetMailslotInfo Lib "kernel32" Alias "GetMailslotInfo" (ByVal hMailslot As Long, lpMaxMessageSize As Long, lpNextSize As Long, lpMessageCount As Long, lpReadTimeout As Long) As Long
Declare Function SetMailslotInfo Lib "kernel32" Alias "SetMailslotInfo" (ByVal hMailslot As Long, ByVal lReadTimeout As Long) As Long
Declare Function MapViewOfFile Lib "kernel32" Alias "MapViewOfFile" (ByVal hFileMappingObject As Long, ByVal dwDesiredAccess As Long, ByVal dwFileOffsetHigh As Long, ByVal dwFileOffsetLow As Long, ByVal dwNumberOfBytesToMap As Long) As Long
Declare Function FlushViewOfFile Lib "kernel32" Alias "FlushViewOfFile" (lpBaseAddress As Any, ByVal dwNumberOfBytesToFlush As Long) As Long
Declare Function UnmapViewOfFile Lib "kernel32" Alias "UnmapViewOfFile" (lpBaseAddress As Any) As Long
Declare Function lstrcmp Lib "kernel32" Alias "lstrcmpA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long
Declare Function lstrcmpi Lib "kernel32" Alias "lstrcmpiA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long
Declare Function lstrlen Lib "kernel32" Alias "lstrlenA" (ByVal lpString As String) As Long
Declare Function lopen Lib "kernel32" Alias "_lopen" (ByVal lpPathName As String, ByVal iReadWrite As Long) As Long
Declare Function lclose Lib "kernel32" Alias "_lclose" (ByVal hFile As Long) As Long
Declare Function lcreat Lib "kernel32" Alias "_lcreat" (ByVal lpPathName As String, ByVal iAttribute As Long) As Long
Declare Function llseek Lib "kernel32" Alias "_llseek" (ByVal hFile As Long, ByVal lOffset As Long, ByVal iOrigin As Long) As Long
Declare Function lread Lib "kernel32" Alias "_lread" (ByVal hFile As Long, lpBuffer As Any, ByVal wBytes As Long) As Long
Declare Function lwrite Lib "kernel32" Alias "_lwrite" (ByVal hFile As Long, ByVal lpBuffer As String, ByVal wBytes As Long) As Long
Declare Function hread Lib "kernel32" Alias "_hread" (ByVal hFile As Long, lpBuffer As Any, ByVal lBytes As Long) As Long
Declare Function hwrite Lib "kernel32" Alias "_hwrite" (ByVal hFile As Long, ByVal lpBuffer As String, ByVal lBytes As Long) As Long
Declare Function TlsAlloc Lib "kernel32" Alias "TlsAlloc" () As Long
Const TLS_OUT_OF_INDEXES = &HFFFF
Declare Function TlsGetValue Lib "kernel32" Alias "TlsGetValue" (ByVal dwTlsIndex As Long) As Long
Declare Function TlsSetValue Lib "kernel32" Alias "TlsSetValue" (ByVal dwTlsIndex As Long, lpTlsValue As Any) As Long
Declare Function TlsFree Lib "kernel32" Alias "TlsFree" (ByVal dwTlsIndex As Long) As Long
Declare Function SleepEx Lib "kernel32" Alias "SleepEx" (ByVal dwMilliseconds As Long, ByVal bAlertable As Long) As Long
Declare Function WaitForSingleObjectEx Lib "kernel32" Alias "WaitForSingleObjectEx" (ByVal hHandle As Long, ByVal dwMilliseconds As Long, ByVal bAlertable As Long) As Long
Declare Function WaitForMultipleObjectsEx Lib "kernel32" Alias "WaitForMultipleObjectsEx" (ByVal nCount As Long, lpHandles As Long, ByVal bWaitAll As Long, ByVal dwMilliseconds As Long, ByVal bAlertable As Long) As Long
Declare Function BackupRead Lib "kernel32" Alias "BackupRead" (ByVal hFile As Long, lpBuffer As Byte, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, ByVal bAbort As Long, ByVal bProcessSecurity As Long, lpContext As Any) As Long
Declare Function BackupSeek Lib "kernel32" Alias "BackupSeek" (ByVal hFile As Long, ByVal dwLowBytesToSeek As Long, ByVal dwHighBytesToSeek As Long, lpdwLowByteSeeked As Long, lpdwHighByteSeeked As Long, lpContext As Long) As Long
Declare Function BackupWrite Lib "kernel32" Alias "BackupWrite" (ByVal hFile As Long, lpBuffer As Byte, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, ByVal bAbort As Long, ByVal bProcessSecurity As Long, lpContext As Long) As Long
' Stream ID type
Type WIN32_STREAM_ID
dwStreamID As Long
dwStreamAttributes As Long
dwStreamSizeLow As Long
dwStreamSizeHigh As Long
dwStreamNameSize As Long
cStreamName As Byte
End Type
' Stream IDs
Const BACKUP_DATA = &H1
Const BACKUP_EA_DATA = &H2
Const BACKUP_SECURITY_DATA = &H3
Const BACKUP_ALTERNATE_DATA = &H4
Const BACKUP_LINK = &H5
' Stream Attributes
Const STREAM_MODIFIED_WHEN_READ = &H1
Const STREAM_CONTAINS_SECURITY = &H2
' Dual Mode API below this line. Dual Mode Types also included.
Const STARTF_USESHOWWINDOW = &H1
Const STARTF_USESIZE = &H2
Const STARTF_USEPOSITION = &H4
Const STARTF_USECOUNTCHARS = &H8
Const STARTF_USEFILLATTRIBUTE = &H10
Const STARTF_RUNFULLSCREEN = &H20 ' ignored for non-x86 platforms
Const STARTF_FORCEONFEEDBACK = &H40
Const STARTF_FORCEOFFFEEDBACK = &H80
Const STARTF_USESTDHANDLES = &H100
Type STARTUPINFO
cb As Long
lpReserved As String
lpDesktop As String
lpTitle As String
dwX As Long
dwY As Long
dwXSize As Long
dwYSize As Long
dwXCountChars As Long
dwYCountChars As Long
dwFillAttribute As Long
dwFlags As Long
wShowWindow As Integer
cbReserved2 As Integer
lpReserved2 As Long
hStdInput As Long
hStdOutput As Long
hStdError As Long
End Type
Const SHUTDOWN_NORETRY = &H1
Type WIN32_FIND_DATA
dwFileAttributes As Long
ftCreationTime As FILETIME
ftLastAccessTime As FILETIME
ftLastWriteTime As FILETIME
nFileSizeHigh As Long
nFileSizeLow As Long
dwReserved0 As Long
dwReserved1 As Long
cFileName As String * MAX_PATH
cAlternate As String * 14
End Type
Declare Function CreateMutex Lib "kernel32" Alias "CreateMutexA" (lpMutexAttributes As SECURITY_ATTRIBUTES, ByVal bInitialOwner As Long, ByVal lpName As String) As Long
Declare Function OpenMutex Lib "kernel32" Alias "OpenMutexA" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal lpName As String) As Long
Declare Function CreateEvent Lib "kernel32" Alias "CreateEventA" (lpEventAttributes As SECURITY_ATTRIBUTES, ByVal bManualReset As Long, ByVal bInitialState As Long, ByVal lpName As String) As Long
Declare Function OpenEvent Lib "kernel32" Alias "OpenEventA" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal lpName As String) As Long
Declare Function CreateSemaphore Lib "kernel32" Alias "CreateSemaphoreA" (lpSemaphoreAttributes As SECURITY_ATTRIBUTES, ByVal lInitialCount As Long, ByVal lMaximumCount As Long, ByVal lpName As String) As Long
Declare Function OpenSemaphore Lib "kernel32" Alias "OpenSemaphoreA" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal lpName As String) As Long
Declare Function CreateFileMapping Lib "kernel32" Alias "CreateFileMappingA" (ByVal hFile As Long, lpFileMappigAttributes As SECURITY_ATTRIBUTES, ByVal flProtect As Long, ByVal dwMaximumSizeHigh As Long, ByVal dwMaximumSizeLow As Long, ByVal lpName As String) As Long
Declare Function OpenFileMapping Lib "kernel32" Alias "OpenFileMappingA" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal lpName As String) As Long
Declare Function GetLogicalDriveStrings Lib "kernel32" Alias "GetLogicalDriveStringsA" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long
Declare Function IsBadReadPtr Lib "kernel32" Alias "IsBadReadPtr" (lp As Any, ByVal ucb As Long) As Long
Declare Function IsBadWritePtr Lib "kernel32" Alias "IsBadWritePtr" (lp As Any, ByVal ucb As Long) As Long
Declare Function IsBadStringPtr Lib "kernel32" Alias "IsBadStringPtrA" (ByVal lpsz As String, ByVal ucchMax As Long) As Long
Declare Function IsBadHugeReadPtr Lib "kernel32" Alias "IsBadHugeReadPtr" (lp As Any, ByVal ucb As Long) As Long
Declare Function IsBadHugeWritePtr Lib "kernel32" Alias "IsBadHugeWritePtr" (lp As Any, ByVal ucb As Long) As Long
Declare Function LookupAccountSid Lib "advapi32.dll" Alias "LookupAccountSidA" (ByVal lpSystemName As String, Sid As Any, ByVal name As String, cbName As Long, ByVal ReferencedDomainName As String, cbReferencedDomainName As Long, peUse As Integer) As Long
Declare Function LookupAccountName Lib "advapi32.dll" Alias "LookupAccountNameA" (ByVal lpSystemName As String, ByVal lpAccountName As String, Sid As Long, cbSid As Long, ByVal ReferencedDomainName As String, cbReferencedDomainName As Long, peUse As Integer) As Long
Declare Function LookupPrivilegeValue Lib "advapi32.dll" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As String, ByVal lpName As String, lpLuid As LARGE_INTEGER) As Long
Declare Function LookupPrivilegeName Lib "advapi32.dll" Alias "LookupPrivilegeNameA" (ByVal lpSystemName As String, lpLuid As LARGE_INTEGER, ByVal lpName As String, cbName As Long) As Long
Declare Function LookupPrivilegeDisplayName Lib "advapi32.dll" Alias "LookupPrivilegeDisplayNameA" (ByVal lpSystemName As String, ByVal lpName As String, ByVal lpDisplayName As String, cbDisplayName As Long, lpLanguageID As Long) As Long
Declare Function AllocateLocallyUniqueId Lib "advapi32.dll" Alias "AllocateLocallyUniqueId" (Luid As LARGE_INTEGER) As Long
Declare Function GetComputerName Lib "kernel32" Alias "GetComputerNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Declare Function SetComputerName Lib "kernel32" Alias "SetComputerNameA" (ByVal lpComputerName As String) As Long
Declare Function GetUserName Lib "advapi32.dll" Alias "GetUserNameA" (ByVal lpBuffer As String, nSize As Long) As Long
' Performance counter API's
Declare Function QueryPerformanceCounter Lib "kernel32" Alias "QueryPerformanceCounter" (lpPerformanceCount As LARGE_INTEGER) As Long
Declare Function QueryPerformanceFrequency Lib "kernel32" Alias "QueryPerformanceFrequency" (lpFrequency As LARGE_INTEGER) As Long
' Abnormal termination codes
Const TC_NORMAL = 0
Const TC_HARDERR = 1
Const TC_GP_TRAP = 2
Const TC_SIGNAL = 3
' Procedure declarations, constant definitions, and macros
Const LOCALE_SSHORTDATE = &H1F ' short date format string
Const LOCALE_SLONGDATE = &H20 ' long date format string
Const LOCALE_STIMEFORMAT = &H1003 ' time format string
Const LOCALE_IDATE = &H21 ' short date format ordering
Const LOCALE_ILDATE = &H22 ' long date format ordering
Const LOCALE_ITIME = &H23 ' time format specifier
Const LOCALE_ICENTURY = &H24 ' century format specifier
Const LOCALE_ITLZERO = &H25 ' leading zeros in time field
Const LOCALE_IDAYLZERO = &H26 ' leading zeros in day field
Const LOCALE_IMONLZERO = &H27 ' leading zeros in month field
Const LOCALE_S1159 = &H28 ' AM designator
Const LOCALE_S2359 = &H29 ' PM designator
Const LOCALE_SDAYNAME1 = &H2A ' long name for Monday
Const LOCALE_SDAYNAME2 = &H2B ' long name for Tuesday
Const LOCALE_SDAYNAME3 = &H2C ' long name for Wednesday
Const LOCALE_SDAYNAME4 = &H2D ' long name for Thursday
Const LOCALE_SDAYNAME5 = &H2E ' long name for Friday
Const LOCALE_SDAYNAME6 = &H2F ' long name for Saturday
Const LOCALE_SDAYNAME7 = &H30 ' long name for Sunday
Const LOCALE_SABBREVDAYNAME1 = &H31 ' abbreviated name for Monday
Const LOCALE_SABBREVDAYNAME2 = &H32 ' abbreviated name for Tuesday
Const LOCALE_SABBREVDAYNAME3 = &H33 ' abbreviated name for Wednesday
Const LOCALE_SABBREVDAYNAME4 = &H34 ' abbreviated name for Thursday
Const LOCALE_SABBREVDAYNAME5 = &H35 ' abbreviated name for Friday
Const LOCALE_SABBREVDAYNAME6 = &H36 ' abbreviated name for Saturday
Const LOCALE_SABBREVDAYNAME7 = &H37 ' abbreviated name for Sunday
Const LOCALE_SMONTHNAME1 = &H38 ' long name for January
Const LOCALE_SMONTHNAME2 = &H39 ' long name for February
Const LOCALE_SMONTHNAME3 = &H3A ' long name for March
Const LOCALE_SMONTHNAME4 = &H3B ' long name for April
Const LOCALE_SMONTHNAME5 = &H3C ' long name for May
Const LOCALE_SMONTHNAME6 = &H3D ' long name for June
Const LOCALE_SMONTHNAME7 = &H3E ' long name for July
Const LOCALE_SMONTHNAME8 = &H3F ' long name for August
Const LOCALE_SMONTHNAME9 = &H40 ' long name for September
Const LOCALE_SMONTHNAME10 = &H41 ' long name for October
Const LOCALE_SMONTHNAME11 = &H42 ' long name for November
Const LOCALE_SMONTHNAME12 = &H43 ' long name for December
Const LOCALE_SABBREVMONTHNAME1 = &H44 ' abbreviated name for January
Const LOCALE_SABBREVMONTHNAME2 = &H45 ' abbreviated name for February
Const LOCALE_SABBREVMONTHNAME3 = &H46 ' abbreviated name for March
Const LOCALE_SABBREVMONTHNAME4 = &H47 ' abbreviated name for April
Const LOCALE_SABBREVMONTHNAME5 = &H48 ' abbreviated name for May
Const LOCALE_SABBREVMONTHNAME6 = &H49 ' abbreviated name for June
Const LOCALE_SABBREVMONTHNAME7 = &H4A ' abbreviated name for July
Const LOCALE_SABBREVMONTHNAME8 = &H4B ' abbreviated name for August
Const LOCALE_SABBREVMONTHNAME9 = &H4C ' abbreviated name for September
Const LOCALE_SABBREVMONTHNAME10 = &H4D ' abbreviated name for October
Const LOCALE_SABBREVMONTHNAME11 = &H4E ' abbreviated name for November
Const LOCALE_SABBREVMONTHNAME12 = &H4F ' abbreviated name for December
Const LOCALE_SABBREVMONTHNAME13 = &H100F
Const LOCALE_SPOSITIVESIGN = &H50 ' positive sign
Const LOCALE_SNEGATIVESIGN = &H51 ' negative sign
Const LOCALE_IPOSSIGNPOSN = &H52 ' positive sign position
Const LOCALE_INEGSIGNPOSN = &H53 ' negative sign position
Const LOCALE_IPOSSYMPRECEDES = &H54 ' mon sym precedes pos amt
Const LOCALE_IPOSSEPBYSPACE = &H55 ' mon sym sep by space from pos amt
Const LOCALE_INEGSYMPRECEDES = &H56 ' mon sym precedes neg amt
Const LOCALE_INEGSEPBYSPACE = &H57 ' mon sym sep by space from neg amt
' Time Flags for GetTimeFormatW.
Const TIME_NOMINUTESORSECONDS = &H1 ' do not use minutes or seconds
Const TIME_NOSECONDS = &H2 ' do not use seconds
Const TIME_NOTIMEMARKER = &H4 ' do not use time marker
Const TIME_FORCE24HOURFORMAT = &H8 ' always use 24 hour format
' Date Flags for GetDateFormatW.
Const DATE_SHORTDATE = &H1 ' use short date picture
Const DATE_LONGDATE = &H2 ' use long date picture
' Code Page Dependent APIs
Declare Function IsValidCodePage Lib "kernel32" Alias "IsValidCodePage" (ByVal CodePage As Long) As Long
Declare Function GetACP Lib "kernel32" Alias "GetACP" () As Long
Declare Function GetOEMCP Lib "kernel32" Alias "GetOEMCP" () As Long
Declare Function GetCPInfo Lib "kernel32" Alias "GetCPInfo" (ByVal CodePage As Long, lpCPInfo As CPINFO) As Long
Declare Function IsDBCSLeadByte Lib "kernel32" Alias "IsDBCSLeadByte" (ByVal bTestChar As Byte) As Long
Declare Function MultiByteToWideChar Lib "kernel32" Alias "MultiByteToWideChar" (ByVal CodePage As Long, ByVal dwFlags As Long, ByVal lpMultiByteStr As String, ByVal cchMultiByte As Long, ByVal lpWideCharStr As String, ByVal cchWideChar As Long) As Long
Declare Function WideCharToMultiByte Lib "kernel32" Alias "WideCharToMultiByte" (ByVal CodePage As Long, ByVal dwFlags As Long, ByVal lpWideCharStr As String, ByVal cchWideChar As Long, ByVal lpMultiByteStr As String, ByVal cchMultiByte As Long, ByVal lpDefaultChar As String, ByVal lpUsedDefaultChar As Long) As Long
' Locale Dependent APIs
Declare Function CompareString Lib "kernel32" Alias "CompareStringA" (ByVal Locale As Long, ByVal dwCmpFlags As Long, ByVal lpString1 As String, ByVal cchCount1 As Long, ByVal lpString2 As String, ByVal cchCount2 As Long) As Long
Declare Function LCMapString Lib "kernel32" Alias "LCMapStringA" (ByVal Locale As Long, ByVal dwMapFlags As Long, ByVal lpSrcStr As String, ByVal cchSrc As Long, ByVal lpDestStr As String, ByVal cchDest As Long) As Long
Declare Function GetLocaleInfo Lib "kernel32" Alias "GetLocaleInfoA" (ByVal Locale As Long, ByVal LCType As Long, ByVal lpLCData As String, ByVal cchData As Long) As Long
Declare Function GetTimeFormat Lib "kernel32" Alias "GetTimeFormatA" (ByVal Locale As Long, ByVal dwFlags As Long, lpTime As SYSTEMTIME, ByVal lpFormat As String, ByVal lpTimeStr As String, ByVal cchTime As Long) As Long
Declare Function GetDateFormat Lib "kernel32" Alias "GetDateFormatA" (ByVal Locale As Long, ByVal dwFlags As Long, lpDate As SYSTEMTIME, ByVal lpFormat As String, ByVal lpDateStr As String, ByVal cchDate As Long) As Long
Declare Function SetThreadLocale Lib "kernel32" Alias "SetThreadLocale" (ByVal Locale As Long) As Long
Declare Function GetSystemDefaultLangID Lib "kernel32" Alias "GetSystemDefaultLangID" () As Integer
Declare Function GetUserDefaultLangID Lib "kernel32" Alias "GetUserDefaultLangID" () As Integer
Declare Function GetSystemDefaultLCID Lib "kernel32" Alias "GetSystemDefaultLCID" () As Long
Declare Function GetUserDefaultLCID Lib "kernel32" Alias "GetUserDefaultLCID" () As Long
' Locale Independent APIs
Declare Function GetStringTypeA Lib "kernel32" Alias "GetStringTypeA" (ByVal lcid As Long, ByVal dwInfoType As Long, ByVal lpSrcStr As String, ByVal cchSrc As Long, lpCharType As Long) As Long
Declare Function FoldString Lib "kernel32" Alias "FoldStringA" (ByVal dwMapFlags As Long, ByVal lpSrcStr As String, ByVal cchSrc As Long, ByVal lpDestStr As String, ByVal cchDest As Long) As Long
DefaultChar(MAX_DEFAULTCHAR) As Byte ' default character
LeadByte(MAX_LEADBYTES) As Byte ' lead byte ranges
End Type
Type NUMBERFMT
NumDigits As Long ' number of decimal digits
LeadingZero As Long ' if leading zero in decimal fields
Grouping As Long ' group size left of decimal
lpDecimalSep As String ' ptr to decimal separator string
lpThousandSep As String ' ptr to thousand separator string
NegativeOrder As Long ' negative number ordering
End Type
'
' * Currency format.
' */
Type CURRENCYFMT
NumDigits As Long ' number of decimal digits
LeadingZero As Long ' if leading zero in decimal fields
Grouping As Long ' group size left of decimal
lpDecimalSep As String ' ptr to decimal separator string
lpThousandSep As String ' ptr to thousand separator string
NegativeOrder As Long ' negative currency ordering
PositiveOrder As Long ' positive currency ordering
lpCurrencySymbol As String ' ptr to currency symbol string
End Type
Declare Function EnumTimeFormats Lib "KERNEL32" Alias "EnumTimeFormats" (ByVal lpTimeFmtEnumProc As Long, ByVal Locale As Long, ByVal dwFlags As Long) As Long
Declare Function EnumDateFormats Lib "KERNEL32" Alias "EnumDateFormats" (ByVal lpDateFmtEnumProc As Long, ByVal Locale As Long, ByVal dwFlags As Long) As Long
Declare Function IsValidLocale Lib "KERNEL32" Alias "IsValidLocale" (ByVal Locale As Long, ByVal dwFlags As Long) As Long
Declare Function ConvertDefaultLocale Lib "KERNEL32" Alias "ConvertDefaultLocale" (ByVal Locale As Long) As Long
Declare Function GetThreadLocale Lib "KERNEL32" Alias "GetThreadLocale" () As Long
Declare Function EnumSystemLocales Lib "KERNEL32" Alias "EnumSystemLocales" (ByVal lpLocaleEnumProc As Long, ByVal dwFlags As Long) As Long
Declare Function EnumSystemCodePages Lib "KERNEL32" Alias "EnumSystemCodePages" (ByVal lpCodePageEnumProc As Long, ByVal dwFlags As Long) As Long
' The following section contains the Public data structures, data types,
' and procedures exported by the NT console subsystem.
Type COORD
x As Integer
y As Integer
End Type
Type SMALL_RECT
Left As Integer
Top As Integer
Right As Integer
Bottom As Integer
End Type
Type KEY_EVENT_RECORD
bKeyDown As Long
wRepeatCount As Integer
wVirtualKeyCode As Integer
wVirtualScanCode As Integer
uChar As Byte
dwControlKeyState As Long
End Type
' ControlKeyState flags
Const RIGHT_ALT_PRESSED = &H1 ' the right alt key is pressed.
Const LEFT_ALT_PRESSED = &H2 ' the left alt key is pressed.
Const RIGHT_CTRL_PRESSED = &H4 ' the right ctrl key is pressed.
Const LEFT_CTRL_PRESSED = &H8 ' the left ctrl key is pressed.
Const SHIFT_PRESSED = &H10 ' the shift key is pressed.
Const NUMLOCK_ON = &H20 ' the numlock light is on.
Const SCROLLLOCK_ON = &H40 ' the scrolllock light is on.
Const CAPSLOCK_ON = &H80 ' the capslock light is on.
Const ENHANCED_KEY = &H100 ' the key is enhanced.
Type MOUSE_EVENT_RECORD
dwMousePosition As COORD
dwButtonState As Long
dwControlKeyState As Long
dwEventFlags As Long
End Type
' ButtonState flags
Const FROM_LEFT_1ST_BUTTON_PRESSED = &H1
Const RIGHTMOST_BUTTON_PRESSED = &H2
Const FROM_LEFT_2ND_BUTTON_PRESSED = &H4
Const FROM_LEFT_3RD_BUTTON_PRESSED = &H8
Const FROM_LEFT_4TH_BUTTON_PRESSED = &H10
' EventFlags
Const MOUSE_MOVED = &H1
Const DOUBLE_CLICK = &H2
Type WINDOW_BUFFER_SIZE_RECORD
dwSize As COORD
End Type
Type MENU_EVENT_RECORD
dwCommandId As Long
End Type
Type FOCUS_EVENT_RECORD
bSetFocus As Long
End Type
' EventType flags:
Const KEY_EVENT = &H1 ' Event contains key event record
Const mouse_eventC = &H2 ' Event contains mouse event record
Const FOREGROUND_BLUE = &H1 ' text color contains blue.
Const FOREGROUND_GREEN = &H2 ' text color contains green.
Const FOREGROUND_RED = &H4 ' text color contains red.
Const FOREGROUND_INTENSITY = &H8 ' text color is intensified.
Const BACKGROUND_BLUE = &H10 ' background color contains blue.
Const BACKGROUND_GREEN = &H20 ' background color contains green.
Const BACKGROUND_RED = &H40 ' background color contains red.
Const BACKGROUND_INTENSITY = &H80 ' background color is intensified.
Type CONSOLE_SCREEN_BUFFER_INFO
dwSize As COORD
dwCursorPosition As COORD
wAttributes As Integer
srWindow As SMALL_RECT
dwMaximumWindowSize As COORD
End Type
Type CONSOLE_CURSOR_INFO
dwSize As Long
bVisible As Long
End Type
Const CTRL_C_EVENT = 0
Const CTRL_BREAK_EVENT = 1
Const CTRL_CLOSE_EVENT = 2
' 3 is reserved!
' 4 is reserved!
Const CTRL_LOGOFF_EVENT = 5
Const CTRL_SHUTDOWN_EVENT = 6
' Input Mode flags:
Const ENABLE_PROCESSED_INPUT = &H1
Const ENABLE_LINE_INPUT = &H2
Const ENABLE_ECHO_INPUT = &H4
Const ENABLE_WINDOW_INPUT = &H8
Const ENABLE_MOUSE_INPUT = &H10
' Output Mode flags:
Const ENABLE_PROCESSED_OUTPUT = &H1
Const ENABLE_WRAP_AT_EOL_OUTPUT = &H2
Declare Function ReadConsoleOutput Lib "kernel32" Alias "ReadConsoleOutputA" (ByVal hConsoleOutput As Long, lpBuffer As CHAR_INFO, dwBufferSize As COORD, dwBufferCoord As COORD, lpReadRegion As SMALL_RECT) As Long
Declare Function WriteConsoleOutput Lib "kernel32" Alias "WriteConsoleOutputA" (ByVal hConsoleOutput As Long, lpBuffer As CHAR_INFO, dwBufferSize As COORD, dwBufferCoord As COORD, lpWriteRegion As SMALL_RECT) As Long
Declare Function ReadConsoleOutputCharacter Lib "kernel32" Alias "ReadConsoleOutputCharacterA" (ByVal hConsoleOutput As Long, ByVal lpCharacter As String, ByVal nLength As Long, dwReadCoord As COORD, lpNumberOfCharsRead As Long) As Long
Declare Function ReadConsoleOutputAttribute Lib "kernel32" Alias "ReadConsoleOutputAttribute" (ByVal hConsoleOutput As Long, lpAttribute As Long, ByVal nLength As Long, dwReadCoord As COORD, lpNumberOfAttrsRead As Long) As Long
Declare Function WriteConsoleOutputCharacter Lib "kernel32" Alias "WriteConsoleOutputCharacterA" (ByVal hConsoleOutput As Long, ByVal lpCharacter As String, ByVal nLength As Long, dwWriteCoord As COORD, lpNumberOfCharsWritten As Long) As Long
Declare Function WriteConsoleOutputAttribute Lib "kernel32" Alias "WriteConsoleOutputAttribute" (ByVal hConsoleOutput As Long, lpAttribute As Integer, ByVal nLength As Long, dwWriteCoord As COORD, lpNumberOfAttrsWritten As Long) As Long
Declare Function FillConsoleOutputCharacter Lib "kernel32" Alias "FillConsoleOutputCharacterA" (ByVal hConsoleOutput As Long, ByVal cCharacter As Byte, ByVal nLength As Long, dwWriteCoord As COORD, lpNumberOfCharsWritten As Long) As Long
Declare Function FillConsoleOutputAttribute Lib "kernel32" Alias "FillConsoleOutputAttribute" (ByVal hConsoleOutput As Long, ByVal wAttribute As Long, ByVal nLength As Long, dwWriteCoord As COORD, lpNumberOfAttrsWritten As Long) As Long
Declare Function GetConsoleMode Lib "kernel32" Alias "GetConsoleMode" (ByVal hConsoleHandle As Long, lpMode As Long) As Long
Declare Function GetNumberOfConsoleInputEvents Lib "kernel32" Alias "GetNumberOfConsoleInputEvents" (ByVal hConsoleInput As Long, lpNumberOfEvents As Long) As Long
Declare Function GetConsoleScreenBufferInfo Lib "kernel32" Alias "GetConsoleScreenBufferInfo" (ByVal hConsoleOutput As Long, lpConsoleScreenBufferInfo As CONSOLE_SCREEN_BUFFER_INFO) As Long
Declare Function GetLargestConsoleWindowSize Lib "kernel32" Alias "GetLargestConsoleWindowSize" (ByVal hConsoleOutput As Long) As COORD
Declare Function GetConsoleCursorInfo Lib "kernel32" Alias "GetConsoleCursorInfo" (ByVal hConsoleOutput As Long, lpConsoleCursorInfo As CONSOLE_CURSOR_INFO) As Long
Declare Function GetNumberOfConsoleMouseButtons Lib "kernel32" Alias "GetNumberOfConsoleMouseButtons" (lpNumberOfMouseButtons As Long) As Long
Declare Function SetConsoleMode Lib "kernel32" Alias "SetConsoleMode" (ByVal hConsoleHandle As Long, ByVal dwMode As Long) As Long
Declare Function SetConsoleActiveScreenBuffer Lib "kernel32" Alias "SetConsoleActiveScreenBuffer" (ByVal hConsoleOutput As Long) As Long
Declare Function FlushConsoleInputBuffer Lib "kernel32" Alias "FlushConsoleInputBuffer" (ByVal hConsoleInput As Long) As Long
Declare Function SetConsoleScreenBufferSize Lib "kernel32" Alias "SetConsoleScreenBufferSize" (ByVal hConsoleOutput As Long, dwSize As COORD) As Long
Declare Function SetConsoleCursorPosition Lib "kernel32" Alias "SetConsoleCursorPosition" (ByVal hConsoleOutput As Long, dwCursorPosition As COORD) As Long
Declare Function SetConsoleCursorInfo Lib "kernel32" Alias "SetConsoleCursorInfo" (ByVal hConsoleOutput As Long, lpConsoleCursorInfo As CONSOLE_CURSOR_INFO) As Long
Declare Function ScrollConsoleScreenBuffer Lib "kernel32" Alias "ScrollConsoleScreenBufferA" (ByVal hConsoleOutput As Long, lpScrollRectangle As SMALL_RECT, lpClipRectangle As SMALL_RECT, dwDestinationOrigin As COORD, lpFill As CHAR_INFO) As Long
Declare Function SetConsoleWindowInfo Lib "kernel32" Alias "SetConsoleWindowInfo" (ByVal hConsoleOutput As Long, ByVal bAbsolute As Long, lpConsoleWindow As SMALL_RECT) As Long
Declare Function SetConsoleTextAttribute Lib "kernel32" Alias "SetConsoleTextAttribute" (ByVal hConsoleOutput As Long, ByVal wAttributes As Long) As Long
Declare Function SetConsoleCtrlHandler Lib "kernel32" Alias "SetConsoleCtrlHandler" (ByVal HandlerRoutine As Long, ByVal Add As Long) As Long
Declare Function GenerateConsoleCtrlEvent Lib "kernel32" Alias "GenerateConsoleCtrlEvent" (ByVal dwCtrlEvent As Long, ByVal dwProcessGroupId As Long) As Long
Declare Function AllocConsole Lib "kernel32" Alias "AllocConsole" () As Long
Declare Function FreeConsole Lib "kernel32" Alias "FreeConsole" () As Long
Declare Function GetConsoleTitle Lib "kernel32" Alias "GetConsoleTitleA" (ByVal lpConsoleTitle As String, ByVal nSize As Long) As Long
Declare Function SetConsoleTitle Lib "kernel32" Alias "SetConsoleTitleA" (ByVal lpConsoleTitle As String) As Long
Declare Function ReadConsole Lib "kernel32" Alias "ReadConsoleA" (ByVal hConsoleInput As Long, lpBuffer As Any, ByVal nNumberOfCharsToRead As Long, lpNumberOfCharsRead As Long, lpReserved As Any) As Long
Declare Function WriteConsole Lib "kernel32" Alias "WriteConsoleA" (ByVal hConsoleOutput As Long, lpBuffer As Any, ByVal nNumberOfCharsToWrite As Long, lpNumberOfCharsWritten As Long, lpReserved As Any) As Long
Const CONSOLE_TEXTMODE_BUFFER = 1
Declare Function CreateConsoleScreenBuffer Lib "kernel32" Alias "CreateConsoleScreenBuffer" (ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As SECURITY_ATTRIBUTES, ByVal dwFlags As Long, lpScreenBufferData As Any) As Long
Declare Function GetConsoleCP Lib "kernel32" Alias "GetConsoleCP" () As Long
Declare Function SetConsoleCP Lib "kernel32" Alias "SetConsoleCP" (ByVal wCodePageID As Long) As Long
Declare Function GetConsoleOutputCP Lib "kernel32" Alias "GetConsoleOutputCP" () As Long
Declare Function SetConsoleOutputCP Lib "kernel32" Alias "SetConsoleOutputCP" (ByVal wCodePageID As Long) As Long
' -------------
' GDI Section
' -------------
' Binary raster ops
Const R2_BLACK = 1 ' 0
Const R2_NOTMERGEPEN = 2 ' DPon
Const R2_MASKNOTPEN = 3 ' DPna
Const R2_NOTCOPYPEN = 4 ' PN
Const R2_MASKPENNOT = 5 ' PDna
Const R2_NOT = 6 ' Dn
Const R2_XORPEN = 7 ' DPx
Const R2_NOTMASKPEN = 8 ' DPan
Const R2_MASKPEN = 9 ' DPa
Const R2_NOTXORPEN = 10 ' DPxn
Const R2_NOP = 11 ' D
Const R2_MERGENOTPEN = 12 ' DPno
Const R2_COPYPEN = 13 ' P
Const R2_MERGEPENNOT = 14 ' PDno
Const R2_MERGEPEN = 15 ' DPo
Const R2_WHITE = 16 ' 1
Const R2_LAST = 16
' Ternary raster operations
Const SRCCOPY = &HCC0020 ' (DWORD) dest = source
Const SRCPAINT = &HEE0086 ' (DWORD) dest = source OR dest
Const SRCAND = &H8800C6 ' (DWORD) dest = source AND dest
Const SRCINVERT = &H660046 ' (DWORD) dest = source XOR dest
Const SRCERASE = &H440328 ' (DWORD) dest = source AND (NOT dest )
Const NOTSRCCOPY = &H330008 ' (DWORD) dest = (NOT source)
Const NOTSRCERASE = &H1100A6 ' (DWORD) dest = (NOT src) AND (NOT dest)
Const MERGECOPY = &HC000CA ' (DWORD) dest = (source AND pattern)
Const MERGEPAINT = &HBB0226 ' (DWORD) dest = (NOT source) OR dest
Const PATCOPY = &HF00021 ' (DWORD) dest = pattern
Const PATPAINT = &HFB0A09 ' (DWORD) dest = DPSnoo
Const PATINVERT = &H5A0049 ' (DWORD) dest = pattern XOR dest
Const DSTINVERT = &H550009 ' (DWORD) dest = (NOT dest)
Declare Function AddFontResource Lib "gdi32" Alias "AddFontResourceA" (ByVal lpFileName As String) As Long
Declare Function AnimatePalette Lib "gdi32" Alias "AnimatePaletteA" (ByVal hPalette As Long, ByVal wStartIndex As Long, ByVal wNumEntries As Long, lpPaletteColors As PALETTEENTRY) As Long
Declare Function Arc Lib "gdi32" Alias "Arc" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long, ByVal X4 As Long, ByVal Y4 As Long) As Long
Declare Function BitBlt Lib "gdi32" Alias "BitBlt" (ByVal hDestDC As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
Declare Function CancelDC Lib "gdi32" Alias "CancelDC" (ByVal hdc As Long) As Long
Declare Function Chord Lib "gdi32" Alias "Chord" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long, ByVal X4 As Long, ByVal Y4 As Long) As Long
Declare Function CloseMetaFile Lib "gdi32" Alias "CloseMetaFile" (ByVal hMF As Long) As Long
Declare Function CombineRgn Lib "gdi32" Alias "CombineRgn" (ByVal hDestRgn As Long, ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long, ByVal nCombineMode As Long) As Long
Declare Function CopyMetaFile Lib "gdi32" Alias "CopyMetaFileA" (ByVal hMF As Long, ByVal lpFileName As String) As Long
Declare Function CreateBitmap Lib "gdi32" Alias "CreateBitmap" (ByVal nWidth As Long, ByVal nHeight As Long, ByVal nPlanes As Long, ByVal nBitCount As Long, lpBits As Any) As Long
Declare Function CreateBitmapIndirect Lib "gdi32" Alias "CreateBitmapIndirect" (lpBitmap As BITMAP) As Long
Declare Function CreateBrushIndirect Lib "gdi32" Alias "CreateBrushIndirect" (lpLogBrush As LOGBRUSH) As Long
Declare Function CreateCompatibleBitmap Lib "gdi32" Alias "CreateCompatibleBitmap" (ByVal hdc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Declare Function CreateDiscardableBitmap Lib "gdi32" Alias "CreateDiscardableBitmap" (ByVal hdc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Declare Function CreateCompatibleDC Lib "gdi32" Alias "CreateCompatibleDC" (ByVal hdc As Long) As Long
Declare Function CreateDC Lib "gdi32" Alias "CreateDCA" (ByVal lpDriverName As String, ByVal lpDeviceName As String, ByVal lpOutput As String, lpInitData As DEVMODE) As Long
Declare Function CreateDIBitmap Lib "gdi32" Alias "CreateDIBitmap" (ByVal hdc As Long, lpInfoHeader As BITMAPINFOHEADER, ByVal dwUsage As Long, lpInitBits As Any, lpInitInfo As BITMAPINFO, ByVal wUsage As Long) As Long
Declare Function CreateDIBPatternBrush Lib "gdi32" Alias "CreateDIBPatternBrush" (ByVal hPackedDIB As Long, ByVal wUsage As Long) As Long
Declare Function CreateDIBPatternBrushPt Lib "gdi32" Alias "CreateDIBPatternBrushPt" (lpPackedDIB As Any, ByVal iUsage As Long) As Long
Declare Function CreateEllipticRgnIndirect Lib "gdi32" Alias "CreateEllipticRgnIndirect" (lpRect As Rect) As Long
Declare Function CreateEllipticRgn Lib "gdi32" Alias "CreateEllipticRgn" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function CreateFontIndirect Lib "gdi32" Alias "CreateFontIndirectA" (lpLogFont As LOGFONT) As Long
Declare Function CreateFont Lib "gdi32" Alias "CreateFontA" (ByVal H As Long, ByVal W As Long, ByVal E As Long, ByVal O As Long, ByVal W As Long, ByVal I As Long, ByVal u As Long, ByVal S As Long, ByVal C As Long, ByVal OP As Long, ByVal CP As Long, ByVal Q As Long, ByVal PAF As Long, ByVal F As String) As Long
Declare Function CreateHatchBrush Lib "gdi32" Alias "CreateHatchBrush" (ByVal nIndex As Long, ByVal crColor As Long) As Long
Declare Function CreateIC Lib "gdi32" Alias "CreateICA" (ByVal lpDriverName As String, ByVal lpDeviceName As String, ByVal lpOutput As String, lpInitData As DEVMODE) As Long
Declare Function CreateMetaFile Lib "gdi32" Alias "CreateMetaFileA" (ByVal lpString As String) As Long
Declare Function CreatePalette Lib "gdi32" Alias "CreatePalette" (lpLogPalette As LOGPALETTE) As Long
Declare Function CreatePen Lib "gdi32" Alias "CreatePen" (ByVal nPenStyle As Long, ByVal nWidth As Long, ByVal crColor As Long) As Long
Declare Function CreatePenIndirect Lib "gdi32" Alias "CreatePenIndirect" (lpLogPen As LOGPEN) As Long
Declare Function CreateRectRgn Lib "gdi32" Alias "CreateRectRgn" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function CreateRectRgnIndirect Lib "gdi32" Alias "CreateRectRgnIndirect" (lpRect As RECT) As Long
Declare Function CreatePolyPolygonRgn Lib "gdi32" Alias "CreatePolyPolygonRgn" (lpPoint As POINTAPI, lpPolyCounts As Long, ByVal nCount As Long, ByVal nPolyFillMode As Long) As Long
Declare Function CreatePatternBrush Lib "gdi32" Alias "CreatePatternBrush" (ByVal hBitmap As Long) As Long
Declare Function CreateRoundRectRgn Lib "gdi32" Alias "CreateRoundRectRgn" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long
Declare Function CreateScalableFontResource Lib "gdi32" Alias "CreateScalableFontResourceA" (ByVal fHidden As Long, ByVal lpszResourceFile As String, ByVal lpszFontFile As String, ByVal lpszCurrentPath As String) As Long
Declare Function CreateSolidBrush Lib "gdi32" Alias "CreateSolidBrush" (ByVal crColor As Long) As Long
Declare Function DeleteDC Lib "gdi32" Alias "DeleteDC" (ByVal hdc As Long) As Long
Declare Function DeleteObject Lib "gdi32" Alias "DeleteObject" (ByVal hObject As Long) As Long
Declare Function DeleteMetaFile Lib "gdi32" Alias "DeleteMetaFile" (ByVal hMF As Long) As Long
' mode selections for the device mode function
Const DM_UPDATE = 1
Const DM_COPY = 2
Const DM_PROMPT = 4
Const DM_MODIFY = 8
Const DM_IN_BUFFER = DM_MODIFY
Const DM_IN_PROMPT = DM_PROMPT
Const DM_OUT_BUFFER = DM_COPY
Const DM_OUT_DEFAULT = DM_UPDATE
' device capabilities indices
Const DC_FIELDS = 1
Const DC_PAPERS = 2
Const DC_PAPERSIZE = 3
Const DC_MINEXTENT = 4
Const DC_MAXEXTENT = 5
Const DC_BINS = 6
Const DC_DUPLEX = 7
Const DC_SIZE = 8
Const DC_EXTRA = 9
Const DC_VERSION = 10
Const DC_DRIVER = 11
Const DC_BINNAMES = 12
Const DC_ENUMRESOLUTIONS = 13
Const DC_FILEDEPENDENCIES = 14
Const DC_TRUETYPE = 15
Const DC_PAPERNAMES = 16
Const DC_ORIENTATION = 17
Const DC_COPIES = 18
' bit fields of the return value (DWORD) for DC_TRUETYPE
Const DCTT_BITMAP = &H1&
Const DCTT_DOWNLOAD = &H2&
Const DCTT_SUBDEV = &H4&
Declare Function DeviceCapabilities Lib "winspool.drv" Alias "DeviceCapabilitiesA" (ByVal lpDeviceName As String, ByVal lpPort As String, ByVal iIndex As Long, ByVal lpOutput As String, lpDevMode As DEVMODE) As Long
Declare Function Ellipse Lib "gdi32" Alias "Ellipse" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function EqualRgn Lib "gdi32" Alias "EqualRgn" (ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long) As Long
Declare Function Escape Lib "gdi32" Alias "Escape" (ByVal hdc As Long, ByVal nEscape As Long, ByVal nCount As Long, ByVal lpInData As String, lpOutData As Any) As Long
Declare Function ExtEscape Lib "gdi32" Alias "ExtEscape" (ByVal hdc As Long, ByVal nEscape As Long, ByVal cbInput As Long, ByVal lpszInData As String, ByVal cbOutput As Long, ByVal lpszOutData As String) As Long
Declare Function DrawEscape Lib "gdi32" Alias "DrawEscape" (ByVal hdc As Long, ByVal nEscape As Long, ByVal cbInput As Long, ByVal lpszInData As String) As Long
Declare Function ExcludeClipRect Lib "gdi32" Alias "ExcludeClipRect" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function ExtCreateRegion Lib "gdi32" Alias "ExtCreateRegion" (lpXform As xform, ByVal nCount As Long, lpRgnData As RGNDATA) As Long
Declare Function ExtFloodFill Lib "gdi32" Alias "ExtFloodFill" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal crColor As Long, ByVal wFillType As Long) As Long
Declare Function FillRgn Lib "gdi32" Alias "FillRgn" (ByVal hdc As Long, ByVal hRgn As Long, ByVal hBrush As Long) As Long
Declare Function FrameRgn Lib "gdi32" Alias "FrameRgn" (ByVal hdc As Long, ByVal hRgn As Long, ByVal hBrush As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Declare Function FloodFill Lib "gdi32" Alias "FloodFill" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal crColor As Long) As Long
Declare Function GetROP2 Lib "gdi32" Alias "GetROP2" (ByVal hdc As Long) As Long
Declare Function GetAspectRatioFilterEx Lib "gdi32" Alias "GetAspectRatioFilterEx" (ByVal hdc As Long, lpAspectRatio As SIZE) As Long
Declare Function GetBkColor Lib "gdi32" Alias "GetBkColor" (ByVal hdc As Long) As Long
Declare Function GetBkMode Lib "gdi32" Alias "GetBkMode" (ByVal hdc As Long) As Long
Declare Function GetBitmapBits Lib "gdi32" Alias "GetBitmapBits" (ByVal hBitmap As Long, ByVal dwCount As Long, lpBits As Any) As Long
Declare Function GetBitmapDimensionEx Lib "gdi32" Alias "GetBitmapDimensionEx" (ByVal hBitmap As Long, lpDimension As SIZE) As Long
Declare Function GetBoundsRect Lib "gdi32" Alias "GetBoundsRect" (ByVal hdc As Long, lprcBounds As RECT, ByVal flags As Long) As Long
Declare Function GetCharWidth Lib "gdi32" Alias "GetCharWidthA" (ByVal hdc As Long, ByVal wFirstChar As Long, ByVal wLastChar As Long, lpBuffer As Long) As Long
Declare Function GetCharWidth32 Lib "gdi32" Alias "GetCharWidth32A" (ByVal hdc As Long, ByVal iFirstChar As Long, ByVal iLastChar As Long, lpBuffer As Long) As Long
Declare Function GetCharWidthFloat Lib "gdi32" Alias "GetCharWidthFloatA" (ByVal hdc As Long, ByVal iFirstChar As Long, ByVal iLastChar As Long, pxBuffer As Double) As Long
Declare Function GetCharABCWidths Lib "gdi32" Alias "GetCharABCWidthsA" (ByVal hdc As Long, ByVal uFirstChar As Long, ByVal uLastChar As Long, lpabc As ABC) As Long
Declare Function GetCharABCWidthsFloat Lib "gdi32" Alias "GetCharABCWidthsFloatA" (ByVal hdc As Long, ByVal iFirstChar As Long, ByVal iLastChar As Long, lpABCF As ABCFLOAT) As Long
Declare Function GetClipBox Lib "gdi32" Alias "GetClipBox" (ByVal hdc As Long, lpRect As RECT) As Long
Declare Function GetClipRgn Lib "gdi32" Alias "GetClipRgn" (ByVal hdc As Long, ByVal hRgn As Long) As Long
Declare Function GetMetaRgn Lib "gdi32" Alias "GetMetaRgn" (ByVal hdc As Long, ByVal hRgn As Long) As Long
Declare Function GetCurrentObject Lib "gdi32" Alias "GetCurrentObject" (ByVal hdc As Long, ByVal uObjectType As Long) As Long
Declare Function GetCurrentPositionEx Lib "gdi32" Alias "GetCurrentPositionEx" (ByVal hdc As Long, lpPoint As POINTAPI) As Long
Declare Function GetDeviceCaps Lib "gdi32" Alias "GetDeviceCaps" (ByVal hdc As Long, ByVal nIndex As Long) As Long
Declare Function GetDIBits Lib "gdi32" Alias "GetDIBits" (ByVal aHDC As Long, ByVal hBitmap As Long, ByVal nStartScan As Long, ByVal nNumScans As Long, lpBits As Any, lpBI As BITMAPINFO, ByVal wUsage As Long) As Long
Declare Function GetFontData Lib "gdi32" Alias "GetFontDataA" (ByVal hdc As Long, ByVal dwTable As Long, ByVal dwOffset As Long, lpvBuffer As Any, ByVal cbData As Long) As Long
Declare Function GetGlyphOutline Lib "gdi32" Alias "GetGlyphOutlineA" (ByVal hdc As Long, ByVal uChar As Long, ByVal fuFormat As Long, lpgm As GLYPHMETRICS, ByVal cbBuffer As Long, lpBuffer As Any, lpmat2 As MAT2) As Long
Declare Function GetGraphicsMode Lib "gdi32" Alias "GetGraphicsMode" (ByVal hdc As Long) As Long
Declare Function GetMapMode Lib "gdi32" Alias "GetMapMode" (ByVal hdc As Long) As Long
Declare Function GetMetaFileBitsEx Lib "gdi32" Alias "GetMetaFileBitsEx" (ByVal hMF As Long, ByVal nSize As Long, lpvData As Any) As Long
Declare Function GetMetaFile Lib "gdi32" Alias "GetMetaFileA" (ByVal lpFileName As String) As Long
Declare Function GetNearestColor Lib "gdi32" Alias "GetNearestColor" (ByVal hdc As Long, ByVal crColor As Long) As Long
Declare Function GetNearestPaletteIndex Lib "gdi32" Alias "GetNearestPaletteIndex" (ByVal hPalette As Long, ByVal crColor As Long) As Long
Declare Function GetObjectType Lib "gdi32" Alias "GetObjectType" (ByVal hgdiobj As Long) As Long
Declare Function GetOutlineTextMetrics Lib "gdi32" Alias "GetOutlineTextMetricsA" (ByVal hdc As Long, ByVal cbData As Long, lpotm As OUTLINETEXTMETRIC) As Long
Declare Function GetPaletteEntries Lib "gdi32" Alias "GetPaletteEntries" (ByVal hPalette As Long, ByVal wStartIndex As Long, ByVal wNumEntries As Long, lpPaletteEntries As PALETTEENTRY) As Long
Declare Function GetPixel Lib "gdi32" Alias "GetPixel" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long) As Long
Declare Function GetPolyFillMode Lib "gdi32" Alias "GetPolyFillMode" (ByVal hdc As Long) As Long
Declare Function GetRasterizerCaps Lib "gdi32" Alias "GetRasterizerCaps" (lpraststat As RASTERIZER_STATUS, ByVal cb As Long) As Long
Declare Function GetRegionData Lib "gdi32" Alias "GetRegionDataA" (ByVal hRgn As Long, ByVal dwCount As Long, lpRgnData As RgnData) As Long
Declare Function GetRgnBox Lib "gdi32" Alias "GetRgnBox" (ByVal hRgn As Long, lpRect As RECT) As Long
Declare Function GetStockObject Lib "gdi32" Alias "GetStockObject" (ByVal nIndex As Long) As Long
Declare Function GetStretchBltMode Lib "gdi32" Alias "GetStretchBltMode" (ByVal hdc As Long) As Long
Declare Function GetSystemPaletteEntries Lib "gdi32" Alias "GetSystemPaletteEntries" (ByVal hdc As Long, ByVal wStartIndex As Long, ByVal wNumEntries As Long, lpPaletteEntries As PALETTEENTRY) As Long
Declare Function GetSystemPaletteUse Lib "gdi32" Alias "GetSystemPaletteUse" (ByVal hdc As Long) As Long
Declare Function GetTextCharacterExtra Lib "gdi32" (ByVal hdc As Long) As Long
Declare Function GetTextAlign Lib "gdi32" Alias "GetTextAlign" (ByVal hdc As Long) As Long
Declare Function GetTextColor Lib "gdi32" Alias "GetTextColor" (ByVal hdc As Long) As Long
Declare Function GetTextExtentPoint Lib "gdi32" Alias "GetTextExtentPointA" (ByVal hdc As Long, ByVal lpszString As String, ByVal cbString As Long, lpSize As SIZE) As Long
Declare Function GetTextExtentPoint32 Lib "gdi32" Alias "GetTextExtentPoint32A" (ByVal hdc As Long, ByVal lpsz As String, ByVal cbString As Long, lpSize As SIZE) As Long
Declare Function GetTextExtentExPoint Lib "gdi32" Alias "GetTextExtentExPointA" (ByVal hdc As Long, ByVal lpszStr As String, ByVal cchString As Long, ByVal nMaxExtent As Long, lpnFit As Long, alpDx As Long, lpSize As SIZE) As Long
Declare Function GetViewportExtEx Lib "gdi32" Alias "GetViewportExtEx" (ByVal hdc As Long, lpSize As SIZE) As Long
Declare Function GetViewportOrgEx Lib "gdi32" Alias "GetViewportOrgEx" (ByVal hdc As Long, lpPoint As POINTAPI) As Long
Declare Function GetWindowExtEx Lib "gdi32" Alias "GetWindowExtEx" (ByVal hdc As Long, lpSize As SIZE) As Long
Declare Function GetWindowOrgEx Lib "gdi32" Alias "GetWindowOrgEx" (ByVal hdc As Long, lpPoint As POINTAPI) As Long
Declare Function IntersectClipRect Lib "gdi32" Alias "IntersectClipRect" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function InvertRgn Lib "gdi32" Alias "InvertRgn" (ByVal hdc As Long, ByVal hRgn As Long) As Long
Declare Function LineTo Lib "gdi32" Alias "LineTo" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long) As Long
Declare Function MaskBlt Lib "gdi32" Alias "MaskBlt" (ByVal hdcDest As Long, ByVal nXDest As Long, ByVal nYDest As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hdcSrc As Long, ByVal nXSrc As Long, ByVal nYSrc As Long, ByVal hbmMask As Long, ByVal xMask As Long, ByVal yMask As Long, ByVal dwRop As Long) As Long
Declare Function PlgBlt Lib "gdi32" Alias "PlgBlt" (ByVal hdcDest As Long, lpPoint As POINTAPI, ByVal hdcSrc As Long, ByVal nXSrc As Long, ByVal nYSrc As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hbmMask As Long, ByVal xMask As Long, ByVal yMask As Long) As Long
Declare Function OffsetClipRgn Lib "gdi32" Alias "OffsetClipRgn" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long) As Long
Declare Function OffsetRgn Lib "gdi32" Alias "OffsetRgn" (ByVal hRgn As Long, ByVal x As Long, ByVal y As Long) As Long
Declare Function PatBlt Lib "gdi32" Alias "PatBlt" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal dwRop As Long) As Long
Declare Function Pie Lib "gdi32" Alias "Pie" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long, ByVal X4 As Long, ByVal Y4 As Long) As Long
Declare Function PlayMetaFile Lib "gdi32" Alias "PlayMetaFile" (ByVal hdc As Long, ByVal hMF As Long) As Long
Declare Function PaintRgn Lib "gdi32" Alias "PaintRgn" (ByVal hdc As Long, ByVal hRgn As Long) As Long
Declare Function PolyPolygon Lib "gdi32" Alias "PolyPolygon" (ByVal hdc As Long, lpPoint As POINTAPI, lpPolyCounts As Long, ByVal nCount As Long) As Long
Declare Function PtInRegion Lib "gdi32" Alias "PtInRegion" (ByVal hRgn As Long, ByVal x As Long, ByVal y As Long) As Long
Declare Function PtVisible Lib "gdi32" Alias "PtVisible" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long) As Long
Declare Function RectVisible Lib "gdi32" Alias "RectVisible" (ByVal hdc As Long, lpRect As RECT) As Long
Declare Function RectInRegion Lib "gdi32" Alias "RectInRegion" (ByVal hRgn As Long, lpRect As RECT) As Long
Declare Function Rectangle Lib "gdi32" Alias "Rectangle" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function RestoreDC Lib "gdi32" Alias "RestoreDC" (ByVal hdc As Long, ByVal nSavedDC As Long) As Long
Declare Function ResetDC Lib "gdi32" Alias "ResetDCA" (ByVal hdc As Long, lpInitData As DEVMODE) As Long
Declare Function RealizePalette Lib "gdi32" Alias "RealizePalette" (ByVal hdc As Long) As Long
Declare Function RemoveFontResource Lib "gdi32" Alias "RemoveFontResourceA" (ByVal lpFileName As String) As Long
Declare Function RoundRect Lib "gdi32" Alias "RoundRect" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long
Declare Function ResizePalette Lib "gdi32" Alias "ResizePalette" (ByVal hPalette As Long, ByVal nNumEntries As Long) As Long
Declare Function SaveDC Lib "gdi32" Alias "SaveDC" (ByVal hdc As Long) As Long
Declare Function SelectClipRgn Lib "gdi32" Alias "SelectClipRgn" (ByVal hdc As Long, ByVal hRgn As Long) As Long
Declare Function ExtSelectClipRgn Lib "gdi32" Alias "ExtSelectClipRgn" (ByVal hdc As Long, ByVal hRgn As Long, ByVal fnMode As Long) As Long
Declare Function SetMetaRgn Lib "gdi32" Alias "SetMetaRgn" (ByVal hdc As Long) As Long
Declare Function SelectObject Lib "gdi32" Alias "SelectObject" (ByVal hdc As Long, ByVal hObject As Long) As Long
Declare Function SelectPalette Lib "gdi32" Alias "SelectPalette" (ByVal hdc As Long, ByVal hPalette As Long, ByVal bForceBackground As Long) As Long
Declare Function SetBkColor Lib "gdi32" Alias "SetBkColor" (ByVal hdc As Long, ByVal crColor As Long) As Long
Declare Function SetBkMode Lib "gdi32" Alias "SetBkMode" (ByVal hdc As Long, ByVal nBkMode As Long) As Long
Declare Function SetBitmapBits Lib "gdi32" Alias "SetBitmapBits" (ByVal hBitmap As Long, ByVal dwCount As Long, lpBits As Any) As Long
Declare Function SetBoundsRect Lib "gdi32" Alias "SetBoundsRect" (ByVal hdc As Long, lprcBounds As RECT, ByVal flags As Long) As Long
Declare Function SetDIBits Lib "gdi32" Alias "SetDIBits" (ByVal hdc As Long, ByVal hBitmap As Long, ByVal nStartScan As Long, ByVal nNumScans As Long, lpBits As Any, lpBI As BITMAPINFO, ByVal wUsage As Long) As Long
Declare Function SetDIBitsToDevice Lib "gdi32" Alias "SetDIBitsToDevice" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal dx As Long, ByVal dy As Long, ByVal SrcX As Long, ByVal SrcY As Long, ByVal Scan As Long, ByVal NumScans As Long, Bits As Any, BitsInfo As BITMAPINFO, ByVal wUsage As Long) As Long
Declare Function SetMapperFlags Lib "gdi32" Alias "SetMapperFlags" (ByVal hdc As Long, ByVal dwFlag As Long) As Long
Declare Function SetGraphicsMode Lib "gdi32" Alias "SetGraphicsMode" (ByVal hdc As Long, ByVal iMode As Long) As Long
Declare Function SetMapMode Lib "gdi32" Alias "SetMapMode" (ByVal hdc As Long, ByVal nMapMode As Long) As Long
Declare Function SetMetaFileBitsEx Lib "gdi32" Alias "SetMetaFileBitsEx" (ByVal nSize As Long, lpData As Byte) As Long
Declare Function SetPaletteEntries Lib "gdi32" Alias "SetPaletteEntries" (ByVal hPalette As Long, ByVal wStartIndex As Long, ByVal wNumEntries As Long, lpPaletteEntries As PALETTEENTRY) As Long
Declare Function SetPixel Lib "gdi32" Alias "SetPixel" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal crColor As Long) As Long
Declare Function SetPixelV Lib "gdi32" Alias "SetPixelV" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal crColor As Long) As Long
Declare Function SetPolyFillMode Lib "gdi32" Alias "SetPolyFillMode" (ByVal hdc As Long, ByVal nPolyFillMode As Long) As Long
Declare Function StretchBlt Lib "gdi32" Alias "StretchBlt" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal nSrcWidth As Long, ByVal nSrcHeight As Long, ByVal dwRop As Long) As Long
Declare Function SetRectRgn Lib "gdi32" Alias "SetRectRgn" (ByVal hRgn As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function StretchDIBits Lib "gdi32" Alias "StretchDIBits" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal dx As Long, ByVal dy As Long, ByVal SrcX As Long, ByVal SrcY As Long, ByVal wSrcWidth As Long, ByVal wSrcHeight As Long, lpBits As Any, lpBitsInfo As BITMAPINFO, ByVal wUsage As Long, ByVal dwRop As Long) As Long
Declare Function SetROP2 Lib "gdi32" Alias "SetROP2" (ByVal hdc As Long, ByVal nDrawMode As Long) As Long
Declare Function SetStretchBltMode Lib "gdi32" Alias "SetStretchBltMode" (ByVal hdc As Long, ByVal nStretchMode As Long) As Long
Declare Function SetSystemPaletteUse Lib "gdi32" Alias "SetSystemPaletteUse" (ByVal hdc As Long, ByVal wUsage As Long) As Long
Declare Function SetTextCharacterExtra Lib "gdi32" Alias "SetTextCharacterExtraA" (ByVal hdc As Long, ByVal nCharExtra As Long) As Long
Declare Function SetTextColor Lib "gdi32" Alias "SetTextColor" (ByVal hdc As Long, ByVal crColor As Long) As Long
Declare Function SetTextAlign Lib "gdi32" Alias "SetTextAlign" (ByVal hdc As Long, ByVal wFlags As Long) As Long
Declare Function SetTextJustification Lib "gdi32" Alias "SetTextJustification" (ByVal hdc As Long, ByVal nBreakExtra As Long, ByVal nBreakCount As Long) As Long
Declare Function UpdateColors Lib "gdi32" Alias "UpdateColors" (ByVal hdc As Long) As Long
Declare Function GetProcAddress Lib "kernel32" Alias "GetProcAddress" (ByVal hModule As Long, ByVal lpProcName As String) As Long
Declare Function PlayMetaFileRecord Lib "gdi32" Alias "PlayMetaFileRecord" (ByVal hdc As Long, lpHandletable As HANDLETABLE, lpMetaRecord As METARECORD, ByVal nHandles As Long) As Long
Declare Function CloseEnhMetaFile Lib "gdi32" Alias "CloseEnhMetaFile" (ByVal hdc As Long) As Long
Declare Function CopyEnhMetaFile Lib "gdi32" Alias "CopyEnhMetaFileA" (ByVal hemfSrc As Long, ByVal lpszFile As String) As Long
Declare Function CreateEnhMetaFile Lib "gdi32" Alias "CreateEnhMetaFileA" (ByVal hdcRef As Long, ByVal lpFileName As String, lpRect As RECT, ByVal lpDescription As String) As Long
Declare Function DeleteEnhMetaFile Lib "gdi32" Alias "DeleteEnhMetaFile" (ByVal hemf As Long) As Long
Declare Function EnumEnhMetaFile Lib "gdi32" Alias "EnumEnhMetaFile" (ByVal hdc As Long, ByVal hemf As Long, ByVal lpEnhMetaFunc As Long, lpData As Any, lpRect As RECT) As Long
Declare Function GetEnhMetaFile Lib "gdi32" Alias "GetEnhMetaFileA" (ByVal lpszMetaFile As String) As Long
Declare Function GetEnhMetaFileBits Lib "gdi32" Alias "GetEnhMetaFileBits" (ByVal hemf As Long, ByVal cbBuffer As Long, lpbBuffer As Byte) As Long
Declare Function GetEnhMetaFileDescription Lib "gdi32" Alias "GetEnhMetaFileDescriptionA" (ByVal hemf As Long, ByVal cchBuffer As Long, ByVal lpszDescription As String) As Long
Declare Function GetEnhMetaFileHeader Lib "gdi32" Alias "GetEnhMetaFileHeader" (ByVal hemf As Long, ByVal cbBuffer As Long, lpemh As ENHMETAHEADER) As Long
Declare Function GetEnhMetaFilePaletteEntries Lib "gdi32" Alias "GetEnhMetaFilePaletteEntries" (ByVal hemf As Long, ByVal cEntries As Long, lppe As PALETTEENTRY) As Long
Declare Function GetWinMetaFileBits Lib "gdi32" Alias "GetWinMetaFileBits" (ByVal hemf As Long, ByVal cbBuffer As Long, lpbBuffer As Byte, ByVal fnMapMode As Long, ByVal hdcRef As Long) As Long
Declare Function PlayEnhMetaFile Lib "gdi32" Alias "PlayEnhMetaFile" (ByVal hdc As Long, ByVal hemf As Long, lpRect As RECT) As Long
Declare Function PlayEnhMetaFileRecord Lib "gdi32" Alias "PlayEnhMetaFileRecord" (ByVal hdc As Long, lpHandletable As HANDLETABLE, lpEnhMetaRecord As ENHMETARECORD, ByVal nHandles As Long) As Long
Declare Function SetEnhMetaFileBits Lib "gdi32" Alias "SetEnhMetaFileBits" (ByVal cbBuffer As Long, lpData As Byte) As Long
Declare Function SetWinMetaFileBits Lib "gdi32" Alias "SetWinMetaFileBits" (ByVal cbBuffer As Long, lpbBuffer As Byte, ByVal hdcRef As Long, lpmfp As METAFILEPICT) As Long
Declare Function GdiComment Lib "gdi32" Alias "GdiComment" (ByVal hdc As Long, ByVal cbSize As Long, lpData As Byte) As Long
Declare Function GetTextMetrics Lib "gdi32" Alias "GetTextMetricsA" (ByVal hdc As Long, lpMetrics As TEXTMETRIC) As Long
Declare Function AngleArc Lib "gdi32" Alias "AngleArc" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal dwRadius As Long, ByVal eStartAngle As Double, ByVal eSweepAngle As Double) As Long
Declare Function PolyPolyline Lib "gdi32" Alias "PolyPolyline" (ByVal hdc As Long, lppt As POINTAPI, lpdwPolyPoints As Long, ByVal cCount As Long) As Long
Declare Function GetWorldTransform Lib "gdi32" Alias "GetWorldTransform" (ByVal hdc As Long, lpXform As xform) As Long
Declare Function SetWorldTransform Lib "gdi32" Alias "SetWorldTransform" (ByVal hdc As Long, lpXform As xform) As Long
Declare Function ModifyWorldTransform Lib "gdi32" Alias "ModifyWorldTransform" (ByVal hdc As Long, lpXform As xform, ByVal iMode As Long) As Long
Declare Function CombineTransform Lib "gdi32" Alias "CombineTransform" (lpxformResult As xform, lpxform1 As xform, lpxform2 As xform) As Long
' Flags value for COLORADJUSTMENT
Const CA_NEGATIVE = &H1
Const CA_LOG_FILTER = &H2
' IlluminantIndex values
Const ILLUMINANT_DEVICE_DEFAULT = 0
Const ILLUMINANT_A = 1
Const ILLUMINANT_B = 2
Const ILLUMINANT_C = 3
Const ILLUMINANT_D50 = 4
Const ILLUMINANT_D55 = 5
Const ILLUMINANT_D65 = 6
Const ILLUMINANT_D75 = 7
Const ILLUMINANT_F2 = 8
Const ILLUMINANT_MAX_INDEX = ILLUMINANT_F2
Const ILLUMINANT_TUNGSTEN = ILLUMINANT_A
Const ILLUMINANT_DAYLIGHT = ILLUMINANT_C
Const ILLUMINANT_FLUORESCENT = ILLUMINANT_F2
Const ILLUMINANT_NTSC = ILLUMINANT_C
' Min and max for RedGamma, GreenGamma, BlueGamma
Const RGB_GAMMA_MIN = 2500 'words
Const RGB_GAMMA_MAX = 65000
' Min and max for ReferenceBlack and ReferenceWhite
Const REFERENCE_WHITE_MIN = 6000 'words
Const REFERENCE_WHITE_MAX = 10000
Const REFERENCE_BLACK_MIN = 0
Const REFERENCE_BLACK_MAX = 4000
' Min and max for Contrast, Brightness, Colorfulness, RedGreenTint
Const COLOR_ADJ_MIN = -100 'shorts
Const COLOR_ADJ_MAX = 100
Type COLORADJUSTMENT
caSize As Integer
caFlags As Integer
caIlluminantIndex As Integer
caRedGamma As Integer
caGreenGamma As Integer
caBlueGamma As Integer
caReferenceBlack As Integer
caReferenceWhite As Integer
caContrast As Integer
caBrightness As Integer
caColorfulness As Integer
caRedGreenTint As Integer
End Type
Declare Function SetColorAdjustment Lib "gdi32" Alias "SetColorAdjustment" (ByVal hdc As Long, lpca As COLORADJUSTMENT) As Long
Declare Function GetColorAdjustment Lib "gdi32" Alias "GetColorAdjustment" (ByVal hdc As Long, lpca As COLORADJUSTMENT) As Long
Declare Function CreateHalftonePalette Lib "gdi32" Alias "CreateHalftonePalette" (ByVal hdc As Long) As Long
Type DOCINFO
cbSize As Long
lpszDocName As String
lpszOutput As String
End Type
Declare Function StartDoc Lib "gdi32" Alias "StartDocA" (ByVal hdc As Long, lpdi As DOCINFO) As Long
Declare Function StartPage Lib "gdi32" Alias "StartPage" (ByVal hdc As Long) As Long
Declare Function EndPage Lib "gdi32" Alias "EndPage" (ByVal hdc As Long) As Long
Declare Function EndDoc Lib "gdi32" Alias "EndDoc" (ByVal hdc As Long) As Long
Declare Function AbortDoc Lib "gdi32" Alias "AbortDoc" (ByVal hdc As Long) As Long
Declare Function AbortPath Lib "gdi32" Alias "AbortPath" (ByVal hdc As Long) As Long
Declare Function ArcTo Lib "gdi32" Alias "ArcTo" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long, ByVal X4 As Long, ByVal Y4 As Long) As Long
Declare Function BeginPath Lib "gdi32" Alias "BeginPath" (ByVal hdc As Long) As Long
Declare Function CloseFigure Lib "gdi32" Alias "CloseFigure" (ByVal hdc As Long) As Long
Declare Function EndPath Lib "gdi32" Alias "EndPath" (ByVal hdc As Long) As Long
Declare Function FillPath Lib "gdi32" Alias "FillPath" (ByVal hdc As Long) As Long
Declare Function FlattenPath Lib "gdi32" Alias "FlattenPath" (ByVal hdc As Long) As Long
Declare Function GetPath Lib "gdi32" Alias "GetPath" (ByVal hdc As Long, lpPoint As POINTAPI, lpTypes As Byte, ByVal nSize As Long) As Long
Declare Function PathToRegion Lib "gdi32" Alias "PathToRegion" (ByVal hdc As Long) As Long
Declare Function PolyDraw Lib "gdi32" Alias "PolyDraw" (ByVal hdc As Long, lppt As POINTAPI, lpbTypes As Byte, ByVal cCount As Long) As Long
Declare Function SelectClipPath Lib "gdi32" Alias "SelectClipPath" (ByVal hdc As Long, ByVal iMode As Long) As Long
Declare Function SetArcDirection Lib "gdi32" Alias "SetArcDirection" (ByVal hdc As Long, ByVal ArcDirection As Long) As Long
Declare Function SetMiterLimit Lib "gdi32" Alias "SetMiterLimit" (ByVal hdc As Long, ByVal eNewLimit As Double, peOldLimit As Double) As Long
Declare Function StrokeAndFillPath Lib "gdi32" Alias "StrokeAndFillPath" (ByVal hdc As Long) As Long
Declare Function StrokePath Lib "gdi32" Alias "StrokePath" (ByVal hdc As Long) As Long
Declare Function WidenPath Lib "gdi32" Alias "WidenPath" (ByVal hdc As Long) As Long
Declare Function ExtCreatePen Lib "gdi32" Alias "ExtCreatePen" (ByVal dwPenStyle As Long, ByVal dwWidth As Long, lplb As LOGBRUSH, ByVal dwStyleCount As Long, lpStyle As Long) As Long
Declare Function GetMiterLimit Lib "gdi32" Alias "GetMiterLimit" (ByVal hdc As Long, peLimit As Double) As Long
Declare Function GetArcDirection Lib "gdi32" Alias "GetArcDirection" (ByVal hdc As Long) As Long
Declare Function GetObject Lib "gdi32" Alias "GetObjectA" (ByVal hObject As Long, ByVal nCount As Long, lpObject As Any) As Long
Declare Function MoveToEx Lib "gdi32" Alias "MoveToEx" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, lpPoint As POINTAPI) As Long
Declare Function TextOut Lib "gdi32" Alias "TextOutA" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal lpString As String, ByVal nCount As Long) As Long
Declare Function ExtTextOut Lib "gdi32" Alias "ExtTextOutA" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal wOptions As Long, lpRect As Rect, ByVal lpString As String, ByVal nCount As Long, lpDx As Long) As Long
Declare Function PolyTextOut Lib "gdi32" Alias "PolyTextOutA" (ByVal hdc As Long, pptxt As POLYTEXT, cStrings As Long) As Long
Declare Function CreatePolygonRgn Lib "gdi32" Alias "CreatePolygonRgn" (lpPoint As POINTAPI, ByVal nCount As Long, ByVal nPolyFillMode As Long) As Long
Declare Function DPtoLP Lib "gdi32" Alias "DPtoLP" (ByVal hdc As Long, lpPoint As POINTAPI, ByVal nCount As Long) As Long
Declare Function LPtoDP Lib "gdi32" Alias "LPtoDP" (ByVal hdc As Long, lpPoint As POINTAPI, ByVal nCount As Long) As Long
Declare Function Polyline Lib "gdi32" Alias "Polyline" (ByVal hdc As Long, lpPoint As POINTAPI, ByVal nCount As Long) As Long
Declare Function Polygon Lib "gdi32" Alias "Polygon" (ByVal hdc As Long, lpPoint As POINTAPI, ByVal nCount As Long) As Long
Declare Function PolyBezier Lib "gdi32" Alias "PolyBezier" (ByVal hdc As Long, lppt As POINTAPI, ByVal cPoints As Long) As Long
Declare Function PolyBezierTo Lib "gdi32" Alias "PolyBezierTo" (ByVal hdc As Long, lppt As POINTAPI, ByVal cCount As Long) As Long
Declare Function PolylineTo Lib "gdi32" Alias "PolylineTo" (ByVal hdc As Long, lppt As POINTAPI, ByVal cCount As Long) As Long
Declare Function SetViewportExtEx Lib "gdi32" Alias "SetViewportExtEx" (ByVal hdc As Long, ByVal nX As Long, ByVal nY As Long, lpSize As SIZE) As Long
Declare Function SetViewportOrgEx Lib "gdi32" Alias "SetViewportOrgEx" (ByVal hdc As Long, ByVal nX As Long, ByVal nY As Long, lpPoint As POINTAPI) As Long
Declare Function SetWindowOrgEx Lib "gdi32" Alias "SetWindowOrgEx" (ByVal hdc As Long, ByVal nX As Long, ByVal nY As Long, lpPoint As POINTAPI) As Long
Declare Function SetWindowExtEx Lib "gdi32" Alias "SetWindowExtEx" (ByVal hdc As Long, ByVal nX As Long, ByVal nY As Long, lpSize As SIZE) As Long
Declare Function OffsetViewportOrgEx Lib "gdi32" Alias "OffsetViewportOrgEx" (ByVal hdc As Long, ByVal nX As Long, ByVal nY As Long, lpPoint As POINTAPI) As Long
Declare Function OffsetWindowOrgEx Lib "gdi32" Alias "OffsetWindowOrgEx" (ByVal hdc As Long, ByVal nX As Long, ByVal nY As Long, lpPoint As POINTAPI) As Long
Declare Function ScaleWindowExtEx Lib "gdi32" Alias "ScaleWindowExtEx" (ByVal hdc As Long, ByVal nXnum As Long, ByVal nXdenom As Long, ByVal nYnum As Long, ByVal nYdenom As Long, lpSize As SIZE) As Long
Declare Function ScaleViewportExtEx Lib "gdi32" Alias "ScaleViewportExtEx" (ByVal hdc As Long, ByVal nXnum As Long, ByVal nXdenom As Long, ByVal nYnum As Long, ByVal nYdenom As Long, lpSize As SIZE) As Long
Declare Function SetBitmapDimensionEx Lib "gdi32" Alias "SetBitmapDimensionEx" (ByVal hbm As Long, ByVal nX As Long, ByVal nY As Long, lpSize As SIZE) As Long
Declare Function SetBrushOrgEx Lib "gdi32" Alias "SetBrushOrgEx" (ByVal hdc As Long, ByVal nXOrg As Long, ByVal nYOrg As Long, lppt As POINTAPI) As Long
Declare Function GetTextFace Lib "gdi32" Alias "GetTextFaceA" (ByVal hdc As Long, ByVal nCount As Long, ByVal lpFacename As String) As Long
Const FONTMAPPER_MAX = 10
Type KERNINGPAIR
wFirst As Integer
wSecond As Integer
iKernAmount As Long
End Type
Declare Function GetKerningPairs Lib "gdi32" Alias "GetKerningPairsA" (ByVal hdc As Long, ByVal cPairs As Long, lpkrnpair As KERNINGPAIR) As Long
Declare Function GetDCOrgEx Lib "gdi32" Alias "GetDCOrgEx" (ByVal hdc As Long, lpPoint As POINTAPI) As Long
Declare Function UnrealizeObject Lib "gdi32" Alias "UnrealizeObject" (ByVal hObject As Long) As Long
Declare Function GdiFlush Lib "gdi32" Alias "GdiFlush" () As Long
Declare Function GdiSetBatchLimit Lib "gdi32" Alias "GdiSetBatchLimit" (ByVal dwLimit As Long) As Long
Declare Function GdiGetBatchLimit Lib "gdi32" Alias "GdiGetBatchLimit" () As Long
' Enhanced metafile constants
Const ENHMETA_SIGNATURE = &H464D4520
' Stock object flag used in the object handle
' index in the enhanced metafile records.
' E.g. The object handle index (META_STOCK_OBJECT Or BLACK_BRUSH)
Const DMICMMETHOD_SYSTEM = 2 ' ICM handled by system
Const DMICMMETHOD_DRIVER = 3 ' ICM handled by driver
Const DMICMMETHOD_DEVICE = 4 ' ICM handled by device
Const DMICMMETHOD_USER = 256 ' Device-specific methods start here
' ICM Intents
Const DMICM_SATURATE = 1 ' Maximize color saturation
Const DMICM_CONTRAST = 2 ' Maximize color contrast
Const DMICM_COLORMETRIC = 3 ' Use specific color metric
Const DMICM_USER = 256 ' Device-specific intents start here
' Media types
Const DMMEDIA_STANDARD = 1 ' Standard paper
Const DMMEDIA_GLOSSY = 2 ' Glossy paper
Const DMMEDIA_TRANSPARENCY = 3 ' Transparency
Const DMMEDIA_USER = 256 ' Device-specific media start here
' Dither types
Const DMDITHER_NONE = 1 ' No dithering
Const DMDITHER_COARSE = 2 ' Dither with a coarse brush
Const DMDITHER_FINE = 3 ' Dither with a fine brush
Const DMDITHER_LINEART = 4 ' LineArt dithering
Const DMDITHER_GRAYSCALE = 5 ' Device does grayscaling
Const DMDITHER_USER = 256 ' Device-specific dithers start here
Const GGO_GRAY2_BITMAP = 4
Const GGO_GRAY4_BITMAP = 5
Const GGO_GRAY8_BITMAP = 6
Const GGO_GLYPH_INDEX = &H80
Const GCP_DBCS = &H1
Const GCP_REORDER = &H2
Const GCP_USEKERNING = &H8
Const GCP_GLYPHSHAPE = &H10
Const GCP_LIGATE = &H20
Const GCP_DIACRITIC = &H100
Const GCP_KASHIDA = &H400
Const GCP_ERROR = &H8000
Const FLI_MASK = &H103B
Const GCP_JUSTIFY = &H10000
Const GCP_NODIACRITICS = &H20000
Const FLI_GLYPHS = &H40000
Const GCP_CLASSIN = &H80000
Const GCP_MAXEXTENT = &H100000
Const GCP_JUSTIFYIN = &H200000
Const GCP_DISPLAYZWG = &H400000
Const GCP_SYMSWAPOFF = &H800000
Const GCP_NUMERICOVERRIDE = &H1000000
Const GCP_NEUTRALOVERRIDE = &H2000000
Const GCP_NUMERICSLATIN = &H4000000
Const GCP_NUMERICSLOCAL = &H8000000
Const GCPCLASS_LATIN = 1
Const GCPCLASS_HEBREW = 2
Const GCPCLASS_ARABIC = 2
Const GCPCLASS_NEUTRAL = 3
Const GCPCLASS_LOCALNUMBER = 4
Const GCPCLASS_LATINNUMBER = 5
Const GCPCLASS_LATINNUMERICTERMINATOR = 6
Const GCPCLASS_LATINNUMERICSEPARATOR = 7
Const GCPCLASS_NUMERICSEPARATOR = 8
Const GCPCLASS_PREBOUNDRTL = &H80
Const GCPCLASS_PREBOUNDLTR = &H40
Type GCP_RESULTS
lStructSize As Long
lpOutString As String
lpOrder As Long
lpDX As Long
lpCaretPos As Long
lpClass As String
lpGlyphs As String
nGlyphs As Long
nMaxFit As Long
End Type
Const DC_BINADJUST = 19
Const DC_EMF_COMPLIANT = 20
Const DC_DATATYPE_PRODUCED = 21
Const DC_COLLATE = 22
Const DCTT_DOWNLOAD_OUTLINE = &H8&
' return values for DC_BINADJUST
Const DCBA_FACEUPNONE = &H0
Const DCBA_FACEUPCENTER = &H1
Const DCBA_FACEUPLEFT = &H2
Const DCBA_FACEUPRIGHT = &H3
Const DCBA_FACEDOWNNONE = &H100
Const DCBA_FACEDOWNCENTER = &H101
Const DCBA_FACEDOWNLEFT = &H102
Const DCBA_FACEDOWNRIGHT = &H103
Declare Function EnumFontFamilies Lib "gdi32" Alias "EnumFontFamiliesA" (ByVal hdc As Long, ByVal lpszFamily As String, ByVal lpEnumFontFamProc As Long, ByVal lParam As Long) As Long
Declare Function EnumFontFamiliesEx Lib "gdi32" Alias "EnumFontFamiliesExA" (ByVal hdc As Long, lpLogFont As LOGFONT, ByVal lpEnumFontProc As Long, ByVal lParam As Long, ByVal dw As Long) As Long
Declare Function GetTextCharset Lib "gdi32" Alias "GetTextCharset" (ByVal hdc As Long) As Long
Declare Function GetTextCharsetInfo Lib "gdi32" Alias "GetTextCharsetInfo" (ByVal hdc As Long, lpSig As FONTSIGNATURE, ByVal dwFlags As Long) As Long
Declare Function TranslateCharsetInfo Lib "gdi32" Alias "TranslateCharsetInfo" (lpSrc As Long, lpcs As CHARSETINFO, ByVal dwFlags As Long) As Long
Declare Function GetFontLanguageInfo Lib "gdi32" Alias "GetFontLanguageInfo" (ByVal hdc As Long) As Long
Declare Function GetCharacterPlacement Lib "gdi32" Alias " GetCharacterPlacementA" (ByVal hdc As Long, ByVal lpsz As String, ByVal n1 As Long, ByVal n2 As Long, lpGcpResults As GCP_RESULTS, ByVal dw As Long) As Long
Const ICM_OFF = 1
Const ICM_ON = 2
Const ICM_QUERY = 3
Type CIEXYZ
ciexyzX As Long
ciexyzY As Long
ciexyzZ As Long
End Type
Type CIEXYZTRIPLE
ciexyzRed As CIEXYZ
ciexyzGreen As CIEXYZ
ciexyBlue As CIEXYZ
End Type
Type LOGCOLORSPACE
lcsSignature As Long
lcsVersion As Long
lcsSize As Long
lcsCSType As Long
lcsIntent As Long
lcsEndPoints As CIEXYZTRIPLE
lcsGammaRed As Long
lcsGammaGreen As Long
lcsGammaBlue As Long
lcsFileName As String * MAX_PATH
End Type
Declare Function SetICMMode Lib "gdi32" Alias "SetICMMode" (ByVal hdc As Long, ByVal n As Long) As Long
Declare Function CheckColorsInGamut Lib "gdi32" Alias "CheckColorsInGamut" (ByVal hdc As Long, lpv As Any, lpv2 As Any, ByVal dw As Long) As Long
Declare Function GetLogColorSpace Lib "gdi32" Alias "GetLogColorSpaceA" (ByVal hcolorspace As Long, ByVal lplogcolorspace As LOGCOLORSPACE, ByVal dw As Long) As Long
Declare Function GetColorSpace Lib "gdi32" Alias "GetColorSpace" (ByVal hdc As Long) As Long
Declare Function CreateColorSpace Lib "gdi32" Alias "CreateColorSpaceA" (lplogcolorspace As LOGCOLORSPACE) As Long
Declare Function SetColorSpace Lib "gdi32" Alias "SetColorSpace" (ByVal hdc As Long, ByVal hcolorspace As Long) As Long
Declare Function DeleteColorSpace Lib "gdi32" Alias "DeleteColorSpace" (ByVal hcolorspace As Long) As Long
Declare Function GetICMProfile Lib "gdi32" Alias "GetICMProfileA" (ByVal hdc As Long, ByVal dw As Long, ByVal lpStr As String) As Long
Declare Function SetICMProfile Lib "gdi32" Alias "SetICMProfileA" (ByVal hdc As Long, ByVal lpStr As String) As Long
Declare Function GetDeviceGammaRamp Lib "gdi32" Alias "GetDeviceGammaRamp" (ByVal hdc As Long, lpv As Any) As Long
Declare Function SetDeviceGammaRamp Lib "gdi32" Alias "SetDeviceGammaRamp" (ByVal hdc As Long, lpv As Any) As Long
Declare Function ColorMatchToTarget Lib "gdi32" Alias "ColorMatchToTarget" (ByVal hdc As Long, ByVal hdc2 As Long, ByVal dw As Long) As Long
Declare Function EnumICMProfiles Lib "gdi32" Alias "EnumICMProfilesA" (ByVal hdc As Long, ByVal icmEnumProc As Long, ByVal lParam As Long) As Long
Const EMR_SETICMMODE = 98
Const EMR_CREATECOLORSPACE = 99
Const EMR_SETCOLORSPACE = 100
Const EMR_DELETECOLORSPACE = 101
Type EMRSELECTCOLORSPACE
pEmr As emr
ihCS As Long ' ColorSpace handle index
End Type
Type EMRCREATECOLORSPACE
pEmr As emr
ihCS As Long ' ColorSpace handle index
lcs As LOGCOLORSPACE
End Type
' --------------
' USER Section
' --------------
' Scroll Bar Constants
Const SB_HORZ = 0
Const SB_VERT = 1
Const SB_CTL = 2
Const SB_BOTH = 3
' Scroll Bar Commands
Const SB_LINEUP = 0
Const SB_LINELEFT = 0
Const SB_LINEDOWN = 1
Const SB_LINERIGHT = 1
Const SB_PAGEUP = 2
Const SB_PAGELEFT = 2
Const SB_PAGEDOWN = 3
Const SB_PAGERIGHT = 3
Const SB_THUMBPOSITION = 4
Const SB_THUMBTRACK = 5
Const SB_TOP = 6
Const SB_LEFT = 6
Const SB_BOTTOM = 7
Const SB_RIGHT = 7
Const SB_ENDSCROLL = 8
' ShowWindow() Commands
Const SW_HIDE = 0
Const SW_SHOWNORMAL = 1
Const SW_NORMAL = 1
Const SW_SHOWMINIMIZED = 2
Const SW_SHOWMAXIMIZED = 3
Const SW_MAXIMIZE = 3
Const SW_SHOWNOACTIVATE = 4
Const SW_SHOW = 5
Const SW_MINIMIZE = 6
Const SW_SHOWMINNOACTIVE = 7
Const SW_SHOWNA = 8
Const SW_RESTORE = 9
Const SW_SHOWDEFAULT = 10
Const SW_MAX = 10
' Old ShowWindow() Commands
Const HIDE_WINDOW = 0
Const SHOW_OPENWINDOW = 1
Const SHOW_ICONWINDOW = 2
Const SHOW_FULLSCREEN = 3
Const SHOW_OPENNOACTIVATE = 4
' Identifiers for the WM_SHOWWINDOW message
Const SW_PARENTCLOSING = 1
Const SW_OTHERZOOM = 2
Const SW_PARENTOPENING = 3
Const SW_OTHERUNZOOM = 4
' WM_KEYUP/DOWN/CHAR HIWORD(lParam) flags
Const KF_EXTENDED = &H100
Const KF_DLGMODE = &H800
Const KF_MENUMODE = &H1000
Const KF_ALTDOWN = &H2000
Const KF_REPEAT = &H4000
Const KF_UP = &H8000
' Virtual Keys, Standard Set
Const VK_LBUTTON = &H1
Const VK_RBUTTON = &H2
Const VK_CANCEL = &H3
Const VK_MBUTTON = &H4 ' NOT contiguous with L RBUTTON
Const VK_BACK = &H8
Const VK_TAB = &H9
Const VK_CLEAR = &HC
Const VK_RETURN = &HD
Const VK_SHIFT = &H10
Const VK_CONTROL = &H11
Const VK_MENU = &H12
Const VK_PAUSE = &H13
Const VK_CAPITAL = &H14
Const VK_ESCAPE = &H1B
Const VK_SPACE = &H20
Const VK_PRIOR = &H21
Const VK_NEXT = &H22
Const VK_END = &H23
Const VK_HOME = &H24
Const VK_LEFT = &H25
Const VK_UP = &H26
Const VK_RIGHT = &H27
Const VK_DOWN = &H28
Const VK_SELECT = &H29
Const VK_PRINT = &H2A
Const VK_EXECUTE = &H2B
Const VK_SNAPSHOT = &H2C
Const VK_INSERT = &H2D
Const VK_DELETE = &H2E
Const VK_HELP = &H2F
' VK_A thru VK_Z are the same as their ASCII equivalents: 'A' thru 'Z'
' VK_0 thru VK_9 are the same as their ASCII equivalents: '0' thru '9'
Const VK_NUMPAD0 = &H60
Const VK_NUMPAD1 = &H61
Const VK_NUMPAD2 = &H62
Const VK_NUMPAD3 = &H63
Const VK_NUMPAD4 = &H64
Const VK_NUMPAD5 = &H65
Const VK_NUMPAD6 = &H66
Const VK_NUMPAD7 = &H67
Const VK_NUMPAD8 = &H68
Const VK_NUMPAD9 = &H69
Const VK_MULTIPLY = &H6A
Const VK_ADD = &H6B
Const VK_SEPARATOR = &H6C
Const VK_SUBTRACT = &H6D
Const VK_DECIMAL = &H6E
Const VK_DIVIDE = &H6F
Const VK_F1 = &H70
Const VK_F2 = &H71
Const VK_F3 = &H72
Const VK_F4 = &H73
Const VK_F5 = &H74
Const VK_F6 = &H75
Const VK_F7 = &H76
Const VK_F8 = &H77
Const VK_F9 = &H78
Const VK_F10 = &H79
Const VK_F11 = &H7A
Const VK_F12 = &H7B
Const VK_F13 = &H7C
Const VK_F14 = &H7D
Const VK_F15 = &H7E
Const VK_F16 = &H7F
Const VK_F17 = &H80
Const VK_F18 = &H81
Const VK_F19 = &H82
Const VK_F20 = &H83
Const VK_F21 = &H84
Const VK_F22 = &H85
Const VK_F23 = &H86
Const VK_F24 = &H87
Const VK_NUMLOCK = &H90
Const VK_SCROLL = &H91
'
' VK_L VK_R - left and right Alt, Ctrl and Shift virtual keys.
' Used only as parameters to GetAsyncKeyState() and GetKeyState().
' No other API or message will distinguish left and right keys in this way.
' /
Const VK_LSHIFT = &HA0
Const VK_RSHIFT = &HA1
Const VK_LCONTROL = &HA2
Const VK_RCONTROL = &HA3
Const VK_LMENU = &HA4
Const VK_RMENU = &HA5
Const VK_ATTN = &HF6
Const VK_CRSEL = &HF7
Const VK_EXSEL = &HF8
Const VK_EREOF = &HF9
Const VK_PLAY = &HFA
Const VK_ZOOM = &HFB
Const VK_NONAME = &HFC
Const VK_PA1 = &HFD
Const VK_OEM_CLEAR = &HFE
' SetWindowsHook() codes
Const WH_MIN = (-1)
Const WH_MSGFILTER = (-1)
Const WH_JOURNALRECORD = 0
Const WH_JOURNALPLAYBACK = 1
Const WH_KEYBOARD = 2
Const WH_GETMESSAGE = 3
Const WH_CALLWNDPROC = 4
Const WH_CBT = 5
Const WH_SYSMSGFILTER = 6
Const WH_MOUSE = 7
Const WH_HARDWARE = 8
Const WH_DEBUG = 9
Const WH_SHELL = 10
Const WH_FOREGROUNDIDLE = 11
Const WH_MAX = 11
' Hook Codes
Const HC_ACTION = 0
Const HC_GETNEXT = 1
Const HC_SKIP = 2
Const HC_NOREMOVE = 3
Const HC_NOREM = HC_NOREMOVE
Const HC_SYSMODALON = 4
Const HC_SYSMODALOFF = 5
' CBT Hook Codes
Const HCBT_MOVESIZE = 0
Const HCBT_MINMAX = 1
Const HCBT_QS = 2
Const HCBT_CREATEWND = 3
Const HCBT_DESTROYWND = 4
Const HCBT_ACTIVATE = 5
Const HCBT_CLICKSKIPPED = 6
Const HCBT_KEYSKIPPED = 7
Const HCBT_SYSCOMMAND = 8
Const HCBT_SETFOCUS = 9
' HCBT_ACTIVATE structure pointed to by lParam
Type CBTACTIVATESTRUCT
fMouse As Long
hWndActive As Long
End Type
' WH_MSGFILTER Filter Proc Codes
Const MSGF_DIALOGBOX = 0
Const MSGF_MESSAGEBOX = 1
Const MSGF_MENU = 2
Const MSGF_MOVE = 3
Const MSGF_SIZE = 4
Const MSGF_SCROLLBAR = 5
Const MSGF_NEXTWINDOW = 6
Const MSGF_MAINLOOP = 8
Const MSGF_MAX = 8
Const MSGF_USER = 4096
Const HSHELL_WINDOWCREATED = 1
Const HSHELL_WINDOWDESTROYED = 2
Const HSHELL_ACTIVATESHELLWINDOW = 3
' Message Structure used in Journaling
Type EVENTMSG
message As Long
paramL As Long
paramH As Long
time As Long
hwnd As Long
End Type
Type CWPSTRUCT
lParam As Long
wParam As Long
message As Long
hwnd As Long
End Type
Type DEBUGHOOKINFO
hModuleHook As Long
Reserved As Long
lParam As Long
wParam As Long
code As Long
End Type
Type MOUSEHOOKSTRUCT
pt As POINTAPI
hwnd As Long
wHitTestCode As Long
dwExtraInfo As Long
End Type
' Keyboard Layout API
Const HKL_PREV = 0
Const HKL_NEXT = 1
Const KLF_ACTIVATE = &H1
Const KLF_SUBSTITUTE_OK = &H2
Const KLF_UNLOADPREVIOUS = &H4
Const KLF_REORDER = &H8
' Size of KeyboardLayoutName (number of characters), including nul terminator
Const KL_NAMELENGTH = 9
Declare Function LoadKeyboardLayout Lib "user32" Alias "LoadKeyboardLayoutA" (ByVal pwszKLID As String, ByVal flags As Long) As Long
Declare Function ActivateKeyboardLayout Lib "user32" Alias "ActivateKeyboardLayout" (ByVal HKL As Long, ByVal flags As Long) As Long
Declare Function UnloadKeyboardLayout Lib "user32" Alias "UnloadKeyboardLayout" (ByVal HKL As Long) As Long
Declare Function GetKeyboardLayoutName Lib "user32" Alias "GetKeyboardLayoutNameA" (ByVal pwszKLID As String) As Long
' Desktop-specific access flags
Const DESKTOP_READOBJECTS = &H1&
Const DESKTOP_CREATEWINDOW = &H2&
Const DESKTOP_CREATEMENU = &H4&
Const DESKTOP_HOOKCONTROL = &H8&
Const DESKTOP_JOURNALRECORD = &H10&
Const DESKTOP_JOURNALPLAYBACK = &H20&
Const DESKTOP_ENUMERATE = &H40&
Const DESKTOP_WRITEOBJECTS = &H80&
Declare Function GetThreadDesktop Lib "user32" Alias "GetThreadDesktop" (ByVal dwThread As Long) As Long
' Windowstation-specific access flags
Const WINSTA_ENUMDESKTOPS = &H1&
Const WINSTA_READATTRIBUTES = &H2&
Const WINSTA_ACCESSCLIPBOARD = &H4&
Const WINSTA_CREATEDESKTOP = &H8&
Const WINSTA_WRITEATTRIBUTES = &H10&
Const WINSTA_ACCESSPUBLICATOMS = &H20&
Const WINSTA_EXITWINDOWS = &H40&
Const WINSTA_ENUMERATE = &H100&
Const WINSTA_READSCREEN = &H200&
Declare Function GetProcessWindowStation Lib "user32" Alias "GetProcessWindowStation" () As Long
Declare Function SetUserObjectSecurity Lib "user32" Alias "SetUserObjectSecurity" (ByVal hObj As Long, pSIRequested As Long, pSd As SECURITY_DESCRIPTOR) As Long
Declare Function GetUserObjectSecurity Lib "user32" Alias "GetUserObjectSecurity" (ByVal hObj As Long, pSIRequested As Long, pSd As SECURITY_DESCRIPTOR, ByVal nLength As Long, lpnLengthNeeded As Long) As Long
' Message structure
' Window field offsets for GetWindowLong() and GetWindowWord()
Const GWL_WNDPROC = (-4)
Const GWL_HINSTANCE = (-6)
Const GWL_HWNDPARENT = (-8)
Const GWL_STYLE = (-16)
Const GWL_EXSTYLE = (-20)
Const GWL_USERDATA = (-21)
Const GWL_ID = (-12)
' Class field offsets for GetClassLong() and GetClassWord()
Const GCL_MENUNAME = (-8)
Const GCL_HBRBACKGROUND = (-10)
Const GCL_HCURSOR = (-12)
Const GCL_HICON = (-14)
Const GCL_HMODULE = (-16)
Const GCL_CBWNDEXTRA = (-18)
Const GCL_CBCLSEXTRA = (-20)
Const GCL_WNDPROC = (-24)
Const GCL_STYLE = (-26)
Const GCW_ATOM = (-32)
' Window Messages
Const WM_NULL = &H0
Const WM_CREATE = &H1
Const WM_DESTROY = &H2
Const WM_MOVE = &H3
Const WM_SIZE = &H5
Const WM_ACTIVATE = &H6
'
' WM_ACTIVATE state values
Const WA_INACTIVE = 0
Const WA_ACTIVE = 1
Const WA_CLICKACTIVE = 2
Const WM_SETFOCUS = &H7
Const WM_KILLFOCUS = &H8
Const WM_ENABLE = &HA
Const WM_SETREDRAW = &HB
Const WM_SETTEXT = &HC
Const WM_GETTEXT = &HD
Const WM_GETTEXTLENGTH = &HE
Const WM_PAINT = &HF
Const WM_CLOSE = &H10
Const WM_QUERYENDSESSION = &H11
Const WM_QUIT = &H12
Const WM_QUERYOPEN = &H13
Const WM_ERASEBKGND = &H14
Const WM_SYSCOLORCHANGE = &H15
Const WM_ENDSESSION = &H16
Const WM_SHOWWINDOW = &H18
Const WM_WININICHANGE = &H1A
Const WM_DEVMODECHANGE = &H1B
Const WM_ACTIVATEAPP = &H1C
Const WM_FONTCHANGE = &H1D
Const WM_TIMECHANGE = &H1E
Const WM_CANCELMODE = &H1F
Const WM_SETCURSOR = &H20
Const WM_MOUSEACTIVATE = &H21
Const WM_CHILDACTIVATE = &H22
Const WM_QUEUESYNC = &H23
Const WM_GETMINMAXINFO = &H24
Type MINMAXINFO
ptReserved As POINTAPI
ptMaxSize As POINTAPI
ptMaxPosition As POINTAPI
ptMinTrackSize As POINTAPI
ptMaxTrackSize As POINTAPI
End Type
Const WM_PAINTICON = &H26
Const WM_ICONERASEBKGND = &H27
Const WM_NEXTDLGCTL = &H28
Const WM_SPOOLERSTATUS = &H2A
Const WM_DRAWITEM = &H2B
Const WM_MEASUREITEM = &H2C
Const WM_DELETEITEM = &H2D
Const WM_VKEYTOITEM = &H2E
Const WM_CHARTOITEM = &H2F
Const WM_SETFONT = &H30
Const WM_GETFONT = &H31
Const WM_SETHOTKEY = &H32
Const WM_GETHOTKEY = &H33
Const WM_QUERYDRAGICON = &H37
Const WM_COMPAREITEM = &H39
Const WM_COMPACTING = &H41
Const WM_OTHERWINDOWCREATED = &H42 ' no longer suported
Const WM_OTHERWINDOWDESTROYED = &H43 ' no longer suported
Const WM_COMMNOTIFY = &H44 ' no longer suported
' notifications passed in low word of lParam on WM_COMMNOTIFY messages
Const CN_RECEIVE = &H1
Const CN_TRANSMIT = &H2
Const CN_EVENT = &H4
Const WM_WINDOWPOSCHANGING = &H46
Const WM_WINDOWPOSCHANGED = &H47
Const WM_POWER = &H48
'
' wParam for WM_POWER window message and DRV_POWER driver notification
Const PWR_OK = 1
Const PWR_FAIL = (-1)
Const PWR_SUSPENDREQUEST = 1
Const PWR_SUSPENDRESUME = 2
Const PWR_CRITICALRESUME = 3
Const WM_COPYDATA = &H4A
Const WM_CANCELJOURNAL = &H4B
Type COPYDATASTRUCT
dwData As Long
cbData As Long
lpData As Long
End Type
Const WM_NCCREATE = &H81
Const WM_NCDESTROY = &H82
Const WM_NCCALCSIZE = &H83
Const WM_NCHITTEST = &H84
Const WM_NCPAINT = &H85
Const WM_NCACTIVATE = &H86
Const WM_GETDLGCODE = &H87
Const WM_NCMOUSEMOVE = &HA0
Const WM_NCLBUTTONDOWN = &HA1
Const WM_NCLBUTTONUP = &HA2
Const WM_NCLBUTTONDBLCLK = &HA3
Const WM_NCRBUTTONDOWN = &HA4
Const WM_NCRBUTTONUP = &HA5
Const WM_NCRBUTTONDBLCLK = &HA6
Const WM_NCMBUTTONDOWN = &HA7
Const WM_NCMBUTTONUP = &HA8
Const WM_NCMBUTTONDBLCLK = &HA9
Const WM_KEYFIRST = &H100
Const WM_KEYDOWN = &H100
Const WM_KEYUP = &H101
Const WM_CHAR = &H102
Const WM_DEADCHAR = &H103
Const WM_SYSKEYDOWN = &H104
Const WM_SYSKEYUP = &H105
Const WM_SYSCHAR = &H106
Const WM_SYSDEADCHAR = &H107
Const WM_KEYLAST = &H108
Const WM_INITDIALOG = &H110
Const WM_COMMAND = &H111
Const WM_SYSCOMMAND = &H112
Const WM_TIMER = &H113
Const WM_HSCROLL = &H114
Const WM_VSCROLL = &H115
Const WM_INITMENU = &H116
Const WM_INITMENUPOPUP = &H117
Const WM_MENUSELECT = &H11F
Const WM_MENUCHAR = &H120
Const WM_ENTERIDLE = &H121
Const WM_CTLCOLORMSGBOX = &H132
Const WM_CTLCOLOREDIT = &H133
Const WM_CTLCOLORLISTBOX = &H134
Const WM_CTLCOLORBTN = &H135
Const WM_CTLCOLORDLG = &H136
Const WM_CTLCOLORSCROLLBAR = &H137
Const WM_CTLCOLORSTATIC = &H138
Const WM_MOUSEFIRST = &H200
Const WM_MOUSEMOVE = &H200
Const WM_LBUTTONDOWN = &H201
Const WM_LBUTTONUP = &H202
Const WM_LBUTTONDBLCLK = &H203
Const WM_RBUTTONDOWN = &H204
Const WM_RBUTTONUP = &H205
Const WM_RBUTTONDBLCLK = &H206
Const WM_MBUTTONDOWN = &H207
Const WM_MBUTTONUP = &H208
Const WM_MBUTTONDBLCLK = &H209
Const WM_MOUSELAST = &H209
Const WM_PARENTNOTIFY = &H210
Const WM_ENTERMENULOOP = &H211
Const WM_EXITMENULOOP = &H212
Const WM_MDICREATE = &H220
Const WM_MDIDESTROY = &H221
Const WM_MDIACTIVATE = &H222
Const WM_MDIRESTORE = &H223
Const WM_MDINEXT = &H224
Const WM_MDIMAXIMIZE = &H225
Const WM_MDITILE = &H226
Const WM_MDICASCADE = &H227
Const WM_MDIICONARRANGE = &H228
Const WM_MDIGETACTIVE = &H229
Const WM_MDISETMENU = &H230
Const WM_DROPFILES = &H233
Const WM_MDIREFRESHMENU = &H234
Const WM_CUT = &H300
Const WM_COPY = &H301
Const WM_PASTE = &H302
Const WM_CLEAR = &H303
Const WM_UNDO = &H304
Const WM_RENDERFORMAT = &H305
Const WM_RENDERALLFORMATS = &H306
Const WM_DESTROYCLIPBOARD = &H307
Const WM_DRAWCLIPBOARD = &H308
Const WM_PAINTCLIPBOARD = &H309
Const WM_VSCROLLCLIPBOARD = &H30A
Const WM_SIZECLIPBOARD = &H30B
Const WM_ASKCBFORMATNAME = &H30C
Const WM_CHANGECBCHAIN = &H30D
Const WM_HSCROLLCLIPBOARD = &H30E
Const WM_QUERYNEWPALETTE = &H30F
Const WM_PALETTEISCHANGING = &H310
Const WM_PALETTECHANGED = &H311
Const WM_HOTKEY = &H312
Const WM_PENWINFIRST = &H380
Const WM_PENWINLAST = &H38F
' NOTE: All Message Numbers below 0x0400 are RESERVED.
' Private Window Messages Start Here:
Const WM_USER = &H400
' WM_SYNCTASK Commands
Const ST_BEGINSWP = 0
Const ST_ENDSWP = 1
' WM_NCHITTEST and MOUSEHOOKSTRUCT Mouse Position Codes
Const HTERROR = (-2)
Const HTTRANSPARENT = (-1)
Const HTNOWHERE = 0
Const HTCLIENT = 1
Const HTCAPTION = 2
Const HTSYSMENU = 3
Const HTGROWBOX = 4
Const HTSIZE = HTGROWBOX
Const HTMENU = 5
Const HTHSCROLL = 6
Const HTVSCROLL = 7
Const HTMINBUTTON = 8
Const HTMAXBUTTON = 9
Const HTLEFT = 10
Const HTRIGHT = 11
Const HTTOP = 12
Const HTTOPLEFT = 13
Const HTTOPRIGHT = 14
Const HTBOTTOM = 15
Const HTBOTTOMLEFT = 16
Const HTBOTTOMRIGHT = 17
Const HTBORDER = 18
Const HTREDUCE = HTMINBUTTON
Const HTZOOM = HTMAXBUTTON
Const HTSIZEFIRST = HTLEFT
Const HTSIZELAST = HTBOTTOMRIGHT
' SendMessageTimeout values
Const SMTO_NORMAL = &H0
Const SMTO_BLOCK = &H1
Const SMTO_ABORTIFHUNG = &H2
' WM_MOUSEACTIVATE Return Codes
Const MA_ACTIVATE = 1
Const MA_ACTIVATEANDEAT = 2
Const MA_NOACTIVATE = 3
Const MA_NOACTIVATEANDEAT = 4
Declare Function RegisterWindowMessage Lib "user32" Alias "RegisterWindowMessageA" (ByVal lpString As String) As Long
' WM_SIZE message wParam values
Const SIZE_RESTORED = 0
Const SIZE_MINIMIZED = 1
Const SIZE_MAXIMIZED = 2
Const SIZE_MAXSHOW = 3
Const SIZE_MAXHIDE = 4
' Obsolete constant names
Const SIZENORMAL = SIZE_RESTORED
Const SIZEICONIC = SIZE_MINIMIZED
Const SIZEFULLSCREEN = SIZE_MAXIMIZED
Const SIZEZOOMSHOW = SIZE_MAXSHOW
Const SIZEZOOMHIDE = SIZE_MAXHIDE
' WM_WINDOWPOSCHANGING/CHANGED struct pointed to by lParam
Type WINDOWPOS
hwnd As Long
hWndInsertAfter As Long
x As Long
y As Long
cx As Long
cy As Long
flags As Long
End Type
' WM_NCCALCSIZE return flags
Const WVR_ALIGNTOP = &H10
Const WVR_ALIGNLEFT = &H20
Const WVR_ALIGNBOTTOM = &H40
Const WVR_ALIGNRIGHT = &H80
Const WVR_HREDRAW = &H100
Const WVR_VREDRAW = &H200
Const WVR_REDRAW = (WVR_HREDRAW Or WVR_VREDRAW)
Const WVR_VALIDRECTS = &H400
' Key State Masks for Mouse Messages
Const MK_LBUTTON = &H1
Const MK_RBUTTON = &H2
Const MK_SHIFT = &H4
Const MK_CONTROL = &H8
Const MK_MBUTTON = &H10
' Window Styles
Const WS_OVERLAPPED = &H0&
Const WS_POPUP = &H80000000
Const WS_CHILD = &H40000000
Const WS_MINIMIZE = &H20000000
Const WS_VISIBLE = &H10000000
Const WS_DISABLED = &H8000000
Const WS_CLIPSIBLINGS = &H4000000
Const WS_CLIPCHILDREN = &H2000000
Const WS_MAXIMIZE = &H1000000
Const WS_CAPTION = &HC00000 ' WS_BORDER Or WS_DLGFRAME
Const WS_BORDER = &H800000
Const WS_DLGFRAME = &H400000
Const WS_VSCROLL = &H200000
Const WS_HSCROLL = &H100000
Const WS_SYSMENU = &H80000
Const WS_THICKFRAME = &H40000
Const WS_GROUP = &H20000
Const WS_TABSTOP = &H10000
Const WS_MINIMIZEBOX = &H20000
Const WS_MAXIMIZEBOX = &H10000
Const WS_TILED = WS_OVERLAPPED
Const WS_ICONIC = WS_MINIMIZE
Const WS_SIZEBOX = WS_THICKFRAME
Const WS_OVERLAPPEDWINDOW = (WS_OVERLAPPED Or WS_CAPTION Or WS_SYSMENU Or WS_THICKFRAME Or WS_MINIMIZEBOX Or WS_MAXIMIZEBOX)
Const WS_TILEDWINDOW = WS_OVERLAPPEDWINDOW
'
' Common Window Styles
' /
Const WS_POPUPWINDOW = (WS_POPUP Or WS_BORDER Or WS_SYSMENU)
Const WS_CHILDWINDOW = (WS_CHILD)
' Extended Window Styles
Const WS_EX_DLGMODALFRAME = &H1&
Const WS_EX_NOPARENTNOTIFY = &H4&
Const WS_EX_TOPMOST = &H8&
Const WS_EX_ACCEPTFILES = &H10&
Const WS_EX_TRANSPARENT = &H20&
' Class styles
Const CS_VREDRAW = &H1
Const CS_HREDRAW = &H2
Const CS_KEYCVTWINDOW = &H4
Const CS_DBLCLKS = &H8
Const CS_OWNDC = &H20
Const CS_CLASSDC = &H40
Const CS_PARENTDC = &H80
Const CS_NOKEYCVT = &H100
Const CS_NOCLOSE = &H200
Const CS_SAVEBITS = &H800
Const CS_BYTEALIGNCLIENT = &H1000
Const CS_BYTEALIGNWINDOW = &H2000
Const CS_PUBLICCLASS = &H4000
' Predefined Clipboard Formats
Const CF_TEXT = 1
Const CF_BITMAP = 2
Const CF_METAFILEPICT = 3
Const CF_SYLK = 4
Const CF_DIF = 5
Const CF_TIFF = 6
Const CF_OEMTEXT = 7
Const CF_DIB = 8
Const CF_PALETTE = 9
Const CF_PENDATA = 10
Const CF_RIFF = 11
Const CF_WAVE = 12
Const CF_UNICODETEXT = 13
Const CF_ENHMETAFILE = 14
Const CF_OWNERDISPLAY = &H80
Const CF_DSPTEXT = &H81
Const CF_DSPBITMAP = &H82
Const CF_DSPMETAFILEPICT = &H83
Const CF_DSPENHMETAFILE = &H8E
' "Private" formats don't get GlobalFree()'d
Const CF_PRIVATEFIRST = &H200
Const CF_PRIVATELAST = &H2FF
' "GDIOBJ" formats do get DeleteObject()'d
Const CF_GDIOBJFIRST = &H300
Const CF_GDIOBJLAST = &H3FF
' Defines for the fVirt field of the Accelerator table structure.
Const FVIRTKEY = True ' Assumed to be == TRUE
Const FNOINVERT = &H2
Const FSHIFT = &H4
Const FCONTROL = &H8
Const FALT = &H10
Type ACCEL
fVirt As Byte
key As Integer
cmd As Integer
End Type
Type PAINTSTRUCT
hdc As Long
fErase As Long
rcPaint As Rect
fRestore As Long
fIncUpdate As Long
rgbReserved(32) As Byte
End Type
Type CREATESTRUCT
lpCreateParams As Long
hInstance As Long
hMenu As Long
hWndParent As Long
cy As Long
cx As Long
y As Long
x As Long
style As Long
lpszName As String
lpszClass As String
ExStyle As Long
End Type
' HCBT_CREATEWND parameters pointed to by lParam
Type CBT_CREATEWND
lpcs As CREATESTRUCT
hWndInsertAfter As Long
End Type
Type WINDOWPLACEMENT
Length As Long
flags As Long
showCmd As Long
ptMinPosition As POINTAPI
ptMaxPosition As POINTAPI
rcNormalPosition As Rect
End Type
Const WPF_SETMINPOSITION = &H1
Const WPF_RESTORETOMAXIMIZED = &H2
' Owner draw control types
Const ODT_MENU = 1
Const ODT_LISTBOX = 2
Const ODT_COMBOBOX = 3
Const ODT_BUTTON = 4
' Owner draw actions
Const ODA_DRAWENTIRE = &H1
Const ODA_SELECT = &H2
Const ODA_FOCUS = &H4
' Owner draw state
Const ODS_SELECTED = &H1
Const ODS_GRAYED = &H2
Const ODS_DISABLED = &H4
Const ODS_CHECKED = &H8
Const ODS_FOCUS = &H10
' MEASUREITEMSTRUCT for ownerdraw
Type MEASUREITEMSTRUCT
CtlType As Long
CtlID As Long
itemID As Long
itemWidth As Long
itemHeight As Long
itemData As Long
End Type
' DRAWITEMSTRUCT for ownerdraw
Type DRAWITEMSTRUCT
CtlType As Long
CtlID As Long
itemID As Long
itemAction As Long
itemState As Long
hwndItem As Long
hdc As Long
rcItem As Rect
itemData As Long
End Type
' DELETEITEMSTRUCT for ownerdraw
Type DELETEITEMSTRUCT
CtlType As Long
CtlID As Long
itemID As Long
hwndItem As Long
itemData As Long
End Type
' COMPAREITEMSTRUCT for ownerdraw sorting
Type COMPAREITEMSTRUCT
CtlType As Long
CtlID As Long
hwndItem As Long
itemID1 As Long
itemData1 As Long
itemID2 As Long
itemData2 As Long
End Type
' Message Function Templates
Declare Function GetMessage Lib "user32" Alias "GetMessageA" (lpMsg As MSG, ByVal hwnd As Long, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long) As Long
Declare Function TranslateMessage Lib "user32" Alias "TranslateMessage" (lpMsg As MSG) As Long
Declare Function DispatchMessage Lib "user32" Alias "DispatchMessageA" (lpMsg As MSG) As Long
Declare Function PeekMessage Lib "user32" Alias "PeekMessageA" (lpMsg As MSG, ByVal hwnd As Long, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long, ByVal wRemoveMsg As Long) As Long
' PeekMessage() Options
Const PM_NOREMOVE = &H0
Const PM_REMOVE = &H1
Const PM_NOYIELD = &H2
Declare Function RegisterHotKey Lib "user32" Alias "RegisterHotKey" (ByVal hwnd As Long, ByVal id As Long, ByVal fsModifiers As Long, ByVal vk As Long) As Long
Declare Function UnregisterHotKey Lib "user32" Alias "UnregisterHotKey" (ByVal hwnd As Long, ByVal id As Long) As Long
Const MOD_ALT = &H1
Const MOD_CONTROL = &H2
Const MOD_SHIFT = &H4
Const IDHOT_SNAPWINDOW = (-1) ' SHIFT-PRINTSCRN
Const IDHOT_SNAPDESKTOP = (-2) ' PRINTSCRN
Const EWX_LOGOFF = 0
Const EWX_SHUTDOWN = 1
Const EWX_REBOOT = 2
Const EWX_FORCE = 4
Const READAPI = 0 ' Flags for _lopen
Const WRITEAPI = 1
Const READ_WRITE = 2
Declare Function ExitWindows Lib "user32" Alias "ExitWindows" (ByVal dwReserved As Long, ByVal uReturnCode As Long) As Long
Declare Function ExitWindowsEx Lib "user32" Alias "ExitWindowsEx" (ByVal uFlags As Long, ByVal dwReserved As Long) As Long
Declare Function SwapMouseButton Lib "user32" Alias "SwapMouseButton" (ByVal bSwap As Long) As Long
Declare Function GetMessagePos Lib "user32" Alias "GetMessagePos" () As Long
Declare Function GetMessageTime Lib "user32" Alias "GetMessageTime" () As Long
Declare Function GetMessageExtraInfo Lib "user32" Alias "GetMessageExtraInfo" () As Long
Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Declare Function SendMessageTimeout Lib "user32" Alias "SendMessageTimeoutA" (ByVal hwnd As Long, ByVal msg As Long, ByVal wParam As Long, ByVal lParam As Long, ByVal fuFlags As Long, ByVal uTimeout As Long, lpdwResult As Long) As Long
Declare Function SendNotifyMessage Lib "user32" Alias "SendNotifyMessageA" (ByVal hwnd As Long, ByVal msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function SendMessageCallback Lib "user32" Alias "SendMessageCallbackA" (ByVal hwnd As Long, ByVal msg As Long, ByVal wParam As Long, ByVal lParam As Long, ByVal lpResultCallBack As Long, ByVal dwData As Long) As Long
Declare Function PostMessage Lib "user32" Alias "PostMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function PostThreadMessage Lib "user32" Alias "PostThreadMessageA" (ByVal idThread As Long, ByVal msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
' Special HWND value for use with PostMessage and SendMessage
Const HWND_BROADCAST = &HFFFF&
Type WNDCLASS
style As Long
lpfnwndproc As Long
cbClsextra As Long
cbWndExtra2 As Long
hInstance As Long
hIcon As Long
hCursor As Long
hbrBackground As Long
lpszMenuName As String
lpszClassName As String
End Type
Declare Function AttachThreadInput Lib "user32" Alias "AttachThreadInput" (ByVal idAttach As Long, ByVal idAttachTo As Long, ByVal fAttach As Long) As Long
Declare Function ReplyMessage Lib "user32" Alias "ReplyMessage" (ByVal lReply As Long) As Long
Declare Function WaitMessage Lib "user32" Alias "WaitMessage" () As Long
Declare Function WaitForInputIdle Lib "user32" Alias "WaitForInputIdle" (ByVal hProcess As Long, ByVal dwMilliseconds As Long) As Long
Declare Function DefWindowProc Lib "user32" Alias "DefWindowProcA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Sub PostQuitMessage Lib "user32" Alias "PostQuitMessage" (ByVal nExitCode As Long)
Declare Function InSendMessage Lib "user32" Alias "InSendMessage" () As Long
Private Declare Function InitCommonControls Lib "COMCTL32" () As Long
Private Declare Function ImageList_Create Lib "COMCTL32" (ByVal MinCx As Long, ByVal MinCy As Long, ByVal flags As Long, ByVal cInitial As Long, ByVal cGrow As Long) As Long
Private Declare Function ImageList_AddIcon Lib "COMCTL32" (ByVal himl As Long, ByVal hIcon As Long) As Long
Private Declare Function ImageList_GetIcon Lib "COMCTL32" (ByVal HIMAGELIST As Long, ByVal ImgIndex As Long, hbmMask As Long) As Long
Private Declare Function ImageList_Draw Lib "COMCTL32" (ByVal HIMAGELIST As Long, ByVal ImgIndex As Long, ByVal hDCDest As Long, ByVal xDest As Long, ByVal yDest As Long, ByVal lStyle As Long) As Long
Declare Function GetDoubleClickTime Lib "user32" Alias "GetDoubleClickTime" () As Long
Declare Function SetDoubleClickTime Lib "user32" Alias "SetDoubleClickTime" (ByVal wCount As Long) As Long
Declare Function RegisterClass Lib "user32" Alias "RegisterClassA" (Class As WNDCLASS) As Long
Declare Function UnregisterClass Lib "user32" Alias "UnregisterClassA" (ByVal lpClassName As String, ByVal hInstance As Long) As Long
Declare Function GetClassInfo Lib "user32" Alias "GetClassInfoA" (ByVal hInstance As Long, ByVal lpClassName As String, lpWndClass As WNDCLASS) As Long
Const CW_USEDEFAULT = &H80000000
Const HWND_DESKTOP = 0
Declare Function CreateWindowEx Lib "user32" Alias "CreateWindowExA" (ByVal dwExStyle As Long, ByVal lpClassName As String, ByVal lpWindowName As String, ByVal dwStyle As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hWndParent As Long, ByVal hMenu As Long, ByVal hInstance As Long, lpParam As Any) As Long
Declare Function IsWindow Lib "user32" Alias "IsWindow" (ByVal hwnd As Long) As Long
Declare Function IsMenu Lib "user32" Alias "IsMenu" (ByVal hMenu As Long) As Long
Declare Function IsChild Lib "user32" Alias "IsChild" (ByVal hWndParent As Long, ByVal hwnd As Long) As Long
Declare Function DestroyWindow Lib "user32" Alias "DestroyWindow" (ByVal hwnd As Long) As Long
Declare Function ShowWindow Lib "user32" Alias "ShowWindow" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
Declare Function FlashWindow Lib "user32" Alias "FlashWindow" (ByVal hwnd As Long, ByVal bInvert As Long) As Long
Declare Function ShowOwnedPopups Lib "user32" Alias "ShowOwnedPopups" (ByVal hwnd As Long, ByVal fShow As Long) As Long
Declare Function OpenIcon Lib "user32" Alias "OpenIcon" (ByVal hwnd As Long) As Long
Declare Function CloseWindow Lib "user32" Alias "CloseWindow" (ByVal hwnd As Long) As Long
Declare Function MoveWindow Lib "user32" Alias "MoveWindow" (ByVal hwnd As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal bRepaint As Long) As Long
Declare Function SetWindowPos Lib "user32" Alias "SetWindowPos" (ByVal hwnd As Long, ByVal hWndInsertAfter As Long, ByVal x As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long
Declare Function GetWindowPlacement Lib "user32" Alias "GetWindowPlacement" (ByVal hwnd As Long, lpwndpl As WINDOWPLACEMENT) As Long
Declare Function SetWindowPlacement Lib "user32" Alias "SetWindowPlacement" (ByVal hwnd As Long, lpwndpl As WINDOWPLACEMENT) As Long
Declare Function BeginDeferWindowPos Lib "user32" Alias "BeginDeferWindowPos" (ByVal nNumWindows As Long) As Long
Declare Function DeferWindowPos Lib "user32" Alias "DeferWindowPos" (ByVal hWinPosInfo As Long, ByVal hwnd As Long, ByVal hWndInsertAfter As Long, ByVal x As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long
Declare Function EndDeferWindowPos Lib "user32" Alias "EndDeferWindowPos" (ByVal hWinPosInfo As Long) As Long
Declare Function IsWindowVisible Lib "user32" Alias "IsWindowVisible" (ByVal hwnd As Long) As Long
Declare Function IsIconic Lib "user32" Alias "IsIconic" (ByVal hwnd As Long) As Long
Declare Function AnyPopup Lib "user32" Alias "AnyPopup" () As Long
Declare Function BringWindowToTop Lib "user32" Alias "BringWindowToTop" (ByVal hwnd As Long) As Long
Declare Function IsZoomed Lib "user32" Alias "IsZoomed" (ByVal hwnd As Long) As Long
' SetWindowPos Flags
Const SWP_NOSIZE = &H1
Const SWP_NOMOVE = &H2
Const SWP_NOZORDER = &H4
Const SWP_NOREDRAW = &H8
Const SWP_NOACTIVATE = &H10
Const SWP_FRAMECHANGED = &H20 ' The frame changed: send WM_NCCALCSIZE
Const SWP_SHOWWINDOW = &H40
Const SWP_HIDEWINDOW = &H80
Const SWP_NOCOPYBITS = &H100
Const SWP_NOOWNERZORDER = &H200 ' Don't do owner Z ordering
Const SWP_DRAWFRAME = SWP_FRAMECHANGED
Const SWP_NOREPOSITION = SWP_NOOWNERZORDER
' SetWindowPos() hwndInsertAfter values
Const HWND_TOP = 0
Const HWND_BOTTOM = 1
Const HWND_TOPMOST = -1
Const HWND_NOTOPMOST = -2
Type DLGTEMPLATE
style As Long
dwExtendedStyle As Long
cdit As Integer
x As Integer
y As Integer
cx As Integer
cy As Integer
End Type
Type DLGITEMTEMPLATE
style As Long
dwExtendedStyle As Long
x As Integer
y As Integer
cx As Integer
cy As Integer
id As Integer
End Type
Declare Function EndDialog Lib "user32" Alias "EndDialog" (ByVal hDlg As Long, ByVal nResult As Long) As Long
Declare Function GetDlgItem Lib "user32" Alias "GetDlgItem" (ByVal hDlg As Long, ByVal nIDDlgItem As Long) As Long
Declare Function SetDlgItemInt Lib "user32" Alias "SetDlgItemInt" (ByVal hDlg As Long, ByVal nIDDlgItem As Long, ByVal wValue As Long, ByVal bSigned As Long) As Long
Declare Function GetDlgItemInt Lib "user32" Alias "GetDlgItemInt" (ByVal hDlg As Long, ByVal nIDDlgItem As Long, ByVal lpTranslated As Long, ByVal bSigned As Long) As Long
Declare Function SetDlgItemText Lib "user32" Alias "SetDlgItemTextA" (ByVal hDlg As Long, ByVal nIDDlgItem As Long, ByVal lpString As String) As Long
Declare Function GetDlgItemText Lib "user32" Alias "GetDlgItemTextA" (ByVal hDlg As Long, ByVal nIDDlgItem As Long, ByVal lpString As String, ByVal nMaxCount As Long) As Long
Declare Function CheckDlgButton Lib "user32" Alias "CheckDLGButtonA" (ByVal hDlg As Long, ByVal nIDButton As Long, ByVal wCheck As Long) As Long
Declare Function CheckRadioButton Lib "user32" Alias "CheckRadioButtonA" (ByVal hDlg As Long, ByVal nIDFirstButton As Long, ByVal nIDLastButton As Long, ByVal nIDCheckButton As Long) As Long
Declare Function IsDlgButtonChecked Lib "user32" Alias "IsDlgButtonChecked" (ByVal hDlg As Long, ByVal nIDButton As Long) As Long
Declare Function SendDlgItemMessage Lib "user32" Alias "SendDlgItemMessageA" (ByVal hDlg As Long, ByVal nIDDlgItem As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function GetNextDlgGroupItem Lib "user32" Alias "GetNextDlgGroupItem" (ByVal hDlg As Long, ByVal hCtl As Long, ByVal bPrevious As Long) As Long
Declare Function GetNextDlgTabItem Lib "user32" Alias "GetNextDlgTabItem" (ByVal hDlg As Long, ByVal hCtl As Long, ByVal bPrevious As Long) As Long
Declare Function GetDlgCtrlID Lib "user32" Alias "GetDlgCtrlID" (ByVal hwnd As Long) As Long
Declare Function GetDialogBaseUnits Lib "user32" Alias "GetDialogBaseUnits" () As Long
Declare Function DefDlgProc Lib "user32" Alias "DefDlgProcA" (ByVal hDlg As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Const DLGWINDOWEXTRA = 30 ' Window extra bytes needed for private dialog classes
Declare Function CallMsgFilter Lib "user32" Alias "CallMsgFilterA" (lpMsg As MSG, ByVal ncode As Long) As Long
' Clipboard Manager Functions
Declare Function OpenClipboard Lib "user32" Alias "OpenClipboard" (ByVal hwnd As Long) As Long
Declare Function CloseClipboard Lib "user32" Alias "CloseClipboard" () As Long
Declare Function GetClipboardOwner Lib "user32" Alias "GetClipboardOwner" () As Long
Declare Function SetClipboardViewer Lib "user32" Alias "SetClipboardViewer" (ByVal hwnd As Long) As Long
Declare Function GetClipboardViewer Lib "user32" Alias "GetClipboardViewer" () As Long
Declare Function ChangeClipboardChain Lib "user32" Alias "ChangeClipboardChain" (ByVal hwnd As Long, ByVal hWndNext As Long) As Long
Declare Function SetClipboardData Lib "user32" Alias "SetClipboardDataA" (ByVal wFormat As Long, ByVal hMem As Long) As Long
Declare Function GetClipboardData Lib "user32" Alias "GetClipboardDataA" (ByVal wFormat As Long) As Long
Declare Function RegisterClipboardFormat Lib "user32" Alias "RegisterClipboardFormatA" (ByVal lpString As String) As Long
Declare Function CountClipboardFormats Lib "user32" Alias "CountClipboardFormats" () As Long
Declare Function EnumClipboardFormats Lib "user32" Alias "EnumClipboardFormats" (ByVal wFormat As Long) As Long
Declare Function GetClipboardFormatName Lib "user32" Alias "GetClipboardFormatNameA" (ByVal wFormat As Long, ByVal lpString As String, ByVal nMaxCount As Long) As Long
Declare Function EmptyClipboard Lib "user32" Alias "EmptyClipboard" () As Long
Declare Function IsClipboardFormatAvailable Lib "user32" Alias "IsClipboardFormatAvailable" (ByVal wFormat As Long) As Long
Declare Function GetPriorityClipboardFormat Lib "user32" Alias "GetPriorityClipboardFormat" (lpPriorityList As Long, ByVal nCount As Long) As Long
Declare Function GetOpenClipboardWindow Lib "user32" Alias "GetOpenClipboardWindow" () As Long
Declare Function CharToOem Lib "user32" Alias "CharToOemA" (ByVal lpszSrc As String, ByVal lpszDst As String) As Long
Declare Function OemToChar Lib "user32" Alias "OemToCharA" (ByVal lpszSrc As String, ByVal lpszDst As String) As Long
Declare Function CharToOemBuff Lib "user32" Alias "CharToOemBuffA" (ByVal lpszSrc As String, ByVal lpszDst As String, ByVal cchDstLength As Long) As Long
Declare Function OemToCharBuff Lib "user32" Alias "OemToCharBuffA" (ByVal lpszSrc As String, ByVal lpszDst As String, ByVal cchDstLength As Long) As Long
Declare Function CharUpper Lib "user32" Alias "CharUpperA" (ByVal lpsz As String) As String
Declare Function CharUpperBuff Lib "user32" Alias "CharUpperBuffA" (ByVal lpsz As String, ByVal cchLength As Long) As Long
Declare Function CharLower Lib "user32" Alias "CharLowerA" (ByVal lpsz As String) As String
Declare Function CharLowerBuff Lib "user32" Alias "CharLowerBuffA" (ByVal lpsz As String, ByVal cchLength As Long) As Long
Declare Function CharNext Lib "user32" Alias "CharNextA" (ByVal lpsz As String) As String
Declare Function CharPrev Lib "user32" Alias "CharPrevA" (ByVal lpszStart As String, ByVal lpszCurrent As String) As String
' Language dependent Routines
Declare Function IsCharAlpha Lib "user32" Alias "IsCharAlphaA" (ByVal cChar As Byte) As Long
Declare Function IsCharAlphaNumeric Lib "user32" Alias "IsCharAlphaNumericA" (ByVal cChar As Byte) As Long
Declare Function IsCharUpper Lib "user32" Alias "IsCharUpperA" (ByVal cChar As Byte) As Long
Declare Function IsCharLower Lib "user32" Alias "IsCharLowerA" (ByVal cChar As Byte) As Long
Declare Function SetFocus Lib "user32" Alias "SetFocus" (ByVal hwnd As Long) As Long
Declare Function GetFocus Lib "user32" Alias "GetFocus" () As Long
Declare Function GetActiveWindow Lib "user32" Alias "GetActiveWindow" () As Long
' Keyboard Information Routines
Declare Function GetKBCodePage Lib "user32" Alias "GetKBCodePage" () As Long
Declare Function GetKeyState Lib "user32" Alias "GetKeyState" (ByVal nVirtKey As Long) As Integer
Declare Function GetAsyncKeyState Lib "user32" Alias "GetAsyncKeyState" (ByVal vKey As Long) As Integer
Declare Function GetKeyboardState Lib "user32" Alias "GetKeyboardState" (pbKeyState As Byte) As Long
Declare Function SetKeyboardState Lib "user32" Alias "SetKeyboardState" (lppbKeyState As Byte) As Long
Declare Function GetKeyboardType Lib "user32" Alias "GetKeyboardType" (ByVal nTypeFlag As Long) As Long
Declare Function GetKeyNameText Lib "user32" Alias "GetKeyNameTextA" (ByVal lParam As Long, ByVal lpBuffer As String, ByVal nSize As Long) As Long
Declare Function ToAscii Lib "user32" Alias "ToAscii" (ByVal uVirtKey As Long, ByVal uScanCode As Long, lpbKeyState As Byte, lpwTransKey As Long, ByVal fuState As Long) As Long
Declare Function ToUnicode Lib "user32" Alias "ToUnicode" (ByVal wVirtKey As Long, ByVal wScanCode As Long, lpKeyState As Byte, ByVal pwszBuff As String, ByVal cchBuff As Long, ByVal wFlags As Long) As Long
Declare Function OemKeyScan Lib "user32" Alias "OemKeyScan" (ByVal wOemChar As Long) As Long
Declare Function VkKeyScan Lib "user32" Alias "VkKeyScanA" (ByVal cChar As Byte) As Integer
Const KEYEVENTF_EXTENDEDKEY = &H1
Const KEYEVENTF_KEYUP = &H2
Declare Sub keybd_event Lib "user32" Alias "keybd_event" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
Const MOUSEEVENTF_MOVE = &H1 ' mouse move
Const MOUSEEVENTF_LEFTDOWN = &H2 ' left button down
Const MOUSEEVENTF_LEFTUP = &H4 ' left button up
Const MOUSEEVENTF_RIGHTDOWN = &H8 ' right button down
Const MOUSEEVENTF_RIGHTUP = &H10 ' right button up
Const MOUSEEVENTF_MIDDLEDOWN = &H20 ' middle button down
Const MOUSEEVENTF_MIDDLEUP = &H40 ' middle button up
Declare Sub mouse_event Lib "user32" Alias "mouse_event" (ByVal dwFlags As Long, ByVal dx As Long, ByVal dy As Long, ByVal cButtons As Long, ByVal dwExtraInfo As Long)
Declare Function MapVirtualKey Lib "user32" Alias "MapVirtualKeyA" (ByVal wCode As Long, ByVal wMapType As Long) As Long
Declare Function GetInputState Lib "user32" Alias "GetInputState" () As Long
Declare Function GetQueueStatus Lib "user32" Alias "GetQueueStatus" (ByVal fuFlags As Long) As Long
Declare Function GetCapture Lib "user32" Alias "GetCapture" () As Long
Declare Function SetCapture Lib "user32" Alias "SetCapture" (ByVal hwnd As Long) As Long
Declare Function ReleaseCapture Lib "user32" Alias "ReleaseCapture" () As Long
Declare Function MsgWaitForMultipleObjects Lib "user32" Alias "MsgWaitForMultipleObjects" (ByVal nCount As Long, pHandles As Long, ByVal fWaitAll As Long, ByVal dwMilliseconds As Long, ByVal dwWakeMask As Long) As Long
' GetQueueStatus flags
Const QS_KEY = &H1
Const QS_MOUSEMOVE = &H2
Const QS_MOUSEBUTTON = &H4
Const QS_POSTMESSAGE = &H8
Const QS_TIMER = &H10
Const QS_PAINT = &H20
Const QS_SENDMESSAGE = &H40
Const QS_HOTKEY = &H80
Const QS_MOUSE = (QS_MOUSEMOVE Or QS_MOUSEBUTTON)
Const QS_INPUT = (QS_MOUSE Or QS_KEY)
Const QS_ALLEVENTS = (QS_INPUT Or QS_POSTMESSAGE Or QS_TIMER Or QS_PAINT Or QS_HOTKEY)
Const QS_ALLINPUT = (QS_SENDMESSAGE Or QS_PAINT Or QS_TIMER Or QS_POSTMESSAGE Or QS_MOUSEBUTTON Or QS_MOUSEMOVE Or QS_HOTKEY Or QS_KEY)
' Windows Functions
Declare Function KillTimer Lib "user32" Alias "KillTimer" (ByVal hwnd As Long, ByVal nIDEvent As Long) As Long
Declare Function IsWindowUnicode Lib "user32" Alias "IsWindowUnicode" (ByVal hwnd As Long) As Long
Declare Function EnableWindow Lib "user32" Alias "EnableWindow" (ByVal hwnd As Long, ByVal fEnable As Long) As Long
Declare Function IsWindowEnabled Lib "user32" Alias "IsWindowEnabled" (ByVal hwnd As Long) As Long
Declare Function LoadAccelerators Lib "user32" Alias "LoadAcceleratorsA" (ByVal hInstance As Long, ByVal lpTableName As String) As Long
Declare Function CreateAcceleratorTable Lib "user32" Alias "CreateAcceleratorTableA" (lpaccl As ACCEL, ByVal cEntries As Long) As Long
Declare Function DestroyAcceleratorTable Lib "user32" Alias "DestroyAcceleratorTable" (ByVal haccel As Long) As Long
Declare Function CopyAcceleratorTable Lib "user32" Alias "CopyAcceleratorTableA" (ByVal hAccelSrc As Long, lpAccelDst As ACCEL, ByVal cAccelEntries As Long) As Long
Declare Function TranslateAccelerator Lib "user32" Alias "TranslateAcceleratorA" (ByVal hwnd As Long, ByVal hAccTable As Long, lpMsg As MSG) As Long
' GetSystemMetrics() codes
Const SM_CXSCREEN = 0
Const SM_CYSCREEN = 1
Const SM_CXVSCROLL = 2
Const SM_CYHSCROLL = 3
Const SM_CYCAPTION = 4
Const SM_CXBORDER = 5
Const SM_CYBORDER = 6
Const SM_CXDLGFRAME = 7
Const SM_CYDLGFRAME = 8
Const SM_CYVTHUMB = 9
Const SM_CXHTHUMB = 10
Const SM_CXICON = 11
Const SM_CYICON = 12
Const SM_CXCURSOR = 13
Const SM_CYCURSOR = 14
Const SM_CYMENU = 15
Const SM_CXFULLSCREEN = 16
Const SM_CYFULLSCREEN = 17
Const SM_CYKANJIWINDOW = 18
Const SM_MOUSEPRESENT = 19
Const SM_CYVSCROLL = 20
Const SM_CXHSCROLL = 21
Const SM_DEBUG = 22
Const SM_SWAPBUTTON = 23
Const SM_RESERVED1 = 24
Const SM_RESERVED2 = 25
Const SM_RESERVED3 = 26
Const SM_RESERVED4 = 27
Const SM_CXMIN = 28
Const SM_CYMIN = 29
Const SM_CXSIZE = 30
Const SM_CYSIZE = 31
Const SM_CXFRAME = 32
Const SM_CYFRAME = 33
Const SM_CXMINTRACK = 34
Const SM_CYMINTRACK = 35
Const SM_CXDOUBLECLK = 36
Const SM_CYDOUBLECLK = 37
Const SM_CXICONSPACING = 38
Const SM_CYICONSPACING = 39
Const SM_MENUDROPALIGNMENT = 40
Const SM_PENWINDOWS = 41
Const SM_DBCSENABLED = 42
Const SM_CMOUSEBUTTONS = 43
Const SM_CMETRICS = 44
Const SM_CXSIZEFRAME = SM_CXFRAME
Const SM_CYSIZEFRAME = SM_CYFRAME
Const SM_CXFIXEDFRAME = SM_CXDLGFRAME
Const SM_CYFIXEDFRAME = SM_CYDLGFRAME
Declare Function GetSystemMetrics Lib "user32" Alias "GetSystemMetrics" (ByVal nIndex As Long) As Long
Declare Function LoadMenu Lib "user32" Alias "LoadMenuA" (ByVal hInstance As Long, ByVal lpString As String) As Long
Declare Function LoadMenuIndirect Lib "user32" Alias "LoadMenuIndirectA" (ByVal lpMenuTemplate As Long) As Long
Declare Function GetMenu Lib "user32" Alias "GetMenu" (ByVal hwnd As Long) As Long
Declare Function SetMenu Lib "user32" Alias "SetMenu" (ByVal hwnd As Long, ByVal hMenu As Long) As Long
Declare Function HiliteMenuItem Lib "user32" Alias "HiliteMenuItem" (ByVal hwnd As Long, ByVal hMenu As Long, ByVal wIDHiliteItem As Long, ByVal wHilite As Long) As Long
Declare Function GetMenuString Lib "user32" Alias "GetMenuStringA" (ByVal hMenu As Long, ByVal wIDItem As Long, ByVal lpString As String, ByVal nMaxCount As Long, ByVal wFlag As Long) As Long
Declare Function GetMenuState Lib "user32" Alias "GetMenuState" (ByVal hMenu As Long, ByVal wID As Long, ByVal wFlags As Long) As Long
Declare Function DrawMenuBar Lib "user32" Alias "DrawMenuBar" (ByVal hwnd As Long) As Long
Declare Function GetSystemMenu Lib "user32" Alias "GetSystemMenu" (ByVal hwnd As Long, ByVal bRevert As Long) As Long
Declare Function CreateMenu Lib "user32" Alias "CreateMenu" () As Long
Declare Function CreatePopupMenu Lib "user32" Alias "CreatePopupMenu" () As Long
Declare Function DestroyMenu Lib "user32" Alias "DestroyMenu" (ByVal hMenu As Long) As Long
Declare Function CheckMenuItem Lib "user32" Alias "CheckMenuItem" (ByVal hMenu As Long, ByVal wIDCheckItem As Long, ByVal wCheck As Long) As Long
Declare Function EnableMenuItem Lib "user32" Alias "EnableMenuItem" (ByVal hMenu As Long, ByVal wIDEnableItem As Long, ByVal wEnable As Long) As Long
Declare Function GetSubMenu Lib "user32" Alias "GetSubMenu" (ByVal hMenu As Long, ByVal nPos As Long) As Long
Declare Function GetMenuItemID Lib "user32" Alias "GetMenuItemID" (ByVal hMenu As Long, ByVal nPos As Long) As Long
Declare Function GetMenuItemCount Lib "user32" Alias "GetMenuItemCount" (ByVal hMenu As Long) As Long
Declare Function InsertMenu Lib "user32" Alias "InsertMenuA" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long, ByVal wIDNewItem As Long, ByVal lpNewItem As Any) As Long
Declare Function AppendMenu Lib "user32" Alias "AppendMenuA" (ByVal hMenu As Long, ByVal wFlags As Long, ByVal wIDNewItem As Long, ByVal lpNewItem As Any) As Long
Declare Function ModifyMenu Lib "user32" Alias "ModifyMenuA" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long, ByVal wIDNewItem As Long, ByVal lpString As Any) As Long
Declare Function RemoveMenu Lib "user32" Alias "RemoveMenu" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long) As Long
Declare Function DeleteMenu Lib "user32" Alias "DeleteMenu" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long) As Long
Declare Function SetMenuItemBitmaps Lib "user32" Alias "SetMenuItemBitmaps" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long, ByVal hBitmapUnchecked As Long, ByVal hBitmapChecked As Long) As Long
Declare Function GetMenuCheckMarkDimensions Lib "user32" Alias "GetMenuCheckMarkDimensions" () As Long
Declare Function TrackPopupMenu Lib "user32" Alias "TrackPopupMenu" (ByVal hMenu As Long, ByVal wFlags As Long, ByVal x As Long, ByVal y As Long, ByVal nReserved As Long, ByVal hwnd As Long, lprc As Rect) As Long
' Flags for TrackPopupMenu
Const TPM_LEFTBUTTON = &H0&
Const TPM_RIGHTBUTTON = &H2&
Const TPM_LEFTALIGN = &H0&
Const TPM_CENTERALIGN = &H4&
Const TPM_RIGHTALIGN = &H8&
Declare Function DrawIcon Lib "user32" Alias "DrawIcon" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal hIcon As Long) As Long
' DrawText() Format Flags
Const DT_TOP = &H0
Const DT_LEFT = &H0
Const DT_CENTER = &H1
Const DT_RIGHT = &H2
Const DT_VCENTER = &H4
Const DT_BOTTOM = &H8
Const DT_WORDBREAK = &H10
Const DT_SINGLELINE = &H20
Const DT_EXPANDTABS = &H40
Const DT_TABSTOP = &H80
Const DT_NOCLIP = &H100
Const DT_EXTERNALLEADING = &H200
Const DT_CALCRECT = &H400
Const DT_NOPREFIX = &H800
Const DT_INTERNAL = &H1000
Declare Function DrawText Lib "user32" Alias "DrawTextA" (ByVal hdc As Long, ByVal lpStr As String, ByVal nCount As Long, lpRect As RECT, ByVal wFormat As Long) As Long
Declare Function TabbedTextOut Lib "user32" Alias "TabbedTextOutA" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal lpString As String, ByVal nCount As Long, ByVal nTabPositions As Long, lpnTabStopPositions As Long, ByVal nTabOrigin As Long) As Long
Declare Function GetTabbedTextExtent Lib "user32" Alias "GetTabbedTextExtentA" (ByVal hdc As Long, ByVal lpString As String, ByVal nCount As Long, ByVal nTabPositions As Long, lpnTabStopPositions As Long) As Long
Declare Function UpdateWindow Lib "user32" Alias "UpdateWindow" (ByVal hwnd As Long) As Long
Declare Function SetActiveWindow Lib "user32" Alias "SetActiveWindow" (ByVal hwnd As Long) As Long
Declare Function GetForegroundWindow Lib "user32" Alias "GetForegroundWindow" () As Long
Declare Function SetForegroundWindow Lib "user32" Alias "SetForegroundWindow" (ByVal hwnd As Long) As Long
Declare Function WindowFromDC Lib "user32" Alias "WindowFromDC" (ByVal hdc As Long) As Long
Declare Function GetDC Lib "user32" Alias "GetDC" (ByVal hwnd As Long) As Long
Declare Function GetDCEx Lib "user32" Alias "GetDCEx" (ByVal hwnd As Long, ByVal hrgnclip As Long, ByVal fdwOptions As Long) As Long
Const DCX_WINDOW = &H1&
Const DCX_CACHE = &H2&
Const DCX_NORESETATTRS = &H4&
Const DCX_CLIPCHILDREN = &H8&
Const DCX_CLIPSIBLINGS = &H10&
Const DCX_PARENTCLIP = &H20&
Const DCX_EXCLUDERGN = &H40&
Const DCX_INTERSECTRGN = &H80&
Const DCX_EXCLUDEUPDATE = &H100&
Const DCX_INTERSECTUPDATE = &H200&
Const DCX_LOCKWINDOWUPDATE = &H400&
Const DCX_NORECOMPUTE = &H100000
Const DCX_VALIDATE = &H200000
Declare Function GetWindowDC Lib "user32" Alias "GetWindowDC" (ByVal hwnd As Long) As Long
Declare Function ReleaseDC Lib "user32" Alias "ReleaseDC" (ByVal hwnd As Long, ByVal hdc As Long) As Long
Declare Function BeginPaint Lib "user32" Alias "BeginPaint" (ByVal hwnd As Long, lpPaint As PAINTSTRUCT) As Long
Declare Function EndPaint Lib "user32" Alias "EndPaint" (ByVal hwnd As Long, lpPaint As PAINTSTRUCT) As Long
Declare Function GetUpdateRect Lib "user32" Alias "GetUpdateRect" (ByVal hwnd As Long, lpRect As RECT, ByVal bErase As Long) As Long
Declare Function GetUpdateRgn Lib "user32" Alias "GetUpdateRgn" (ByVal hwnd As Long, ByVal hRgn As Long, ByVal fErase As Long) As Long
Declare Function ExcludeUpdateRgn Lib "user32" Alias "ExcludeUpdateRgn" (ByVal hdc As Long, ByVal hwnd As Long) As Long
Declare Function InvalidateRect Lib "user32" Alias "InvalidateRect" (ByVal hwnd As Long, lpRect As RECT, ByVal bErase As Long) As Long
Declare Function ValidateRect Lib "user32" Alias "ValidateRect" (ByVal hwnd As Long, lpRect As RECT) As Long
Declare Function InvalidateRgn Lib "user32" Alias "InvalidateRgn" (ByVal hwnd As Long, ByVal hRgn As Long, ByVal bErase As Long) As Long
Declare Function ValidateRgn Lib "user32" Alias "ValidateRgn" (ByVal hwnd As Long, ByVal hRgn As Long) As Long
Declare Function RedrawWindow Lib "user32" Alias "RedrawWindow" (ByVal hwnd As Long, lprcUpdate As RECT, ByVal hrgnUpdate As Long, ByVal fuRedraw As Long) As Long
Const RDW_INVALIDATE = &H1
Const RDW_INTERNALPAINT = &H2
Const RDW_ERASE = &H4
Const RDW_VALIDATE = &H8
Const RDW_NOINTERNALPAINT = &H10
Const RDW_NOERASE = &H20
Const RDW_NOCHILDREN = &H40
Const RDW_ALLCHILDREN = &H80
Const RDW_UPDATENOW = &H100
Const RDW_ERASENOW = &H200
Const RDW_FRAME = &H400
Const RDW_NOFRAME = &H800
Declare Function LockWindowUpdate Lib "user32" Alias "LockWindowUpdate" (ByVal hwndLock As Long) As Long
Declare Function ScrollWindow Lib "user32" Alias "ScrollWindow" (ByVal hWnd As Long, ByVal XAmount As Long, ByVal YAmount As Long, lpRect As RECT, lpClipRect As RECT) As Long
Declare Function ScrollDC Lib "user32" Alias "ScrollDC" (ByVal hdc As Long, ByVal dx As Long, ByVal dy As Long, lprcScroll As RECT, lprcClip As RECT, ByVal hrgnUpdate As Long, lprcUpdate As RECT) As Long
Declare Function ScrollWindowEx Lib "user32" Alias "ScrollWindowEx" (ByVal hwnd As Long, ByVal dx As Long, ByVal dy As Long, lprcScroll As RECT, lprcClip As RECT, ByVal hrgnUpdate As Long, lprcUpdate As RECT, ByVal fuScroll As Long) As Long
Const SW_SCROLLCHILDREN = &H1
Const SW_INVALIDATE = &H2
Const SW_ERASE = &H4
Declare Function SetScrollPos Lib "user32" Alias "SetScrollPos" (ByVal hwnd As Long, ByVal nBar As Long, ByVal nPos As Long, ByVal bRedraw As Long) As Long
Declare Function GetScrollPos Lib "user32" Alias "GetScrollPos" (ByVal hwnd As Long, ByVal nBar As Long) As Long
Declare Function SetScrollRange Lib "user32" Alias "SetScrollRange" (ByVal hwnd As Long, ByVal nBar As Long, ByVal nMinPos As Long, ByVal nMaxPos As Long, ByVal bRedraw As Long) As Long
Declare Function GetScrollRange Lib "user32" Alias "GetScrollRange" (ByVal hwnd As Long, ByVal nBar As Long, lpMinPos As Long, lpMaxPos As Long) As Long
Declare Function ShowScrollBar Lib "user32" Alias "ShowScrollBar" (ByVal hwnd As Long, ByVal wBar As Long, ByVal bShow As Long) As Long
Declare Function EnableScrollBar Lib "user32" Alias "EnableScrollBar" (ByVal hwnd As Long, ByVal wSBflags As Long, ByVal wArrows As Long) As Long
' EnableScrollBar() flags
Const ESB_ENABLE_BOTH = &H0
Const ESB_DISABLE_BOTH = &H3
Const ESB_DISABLE_LEFT = &H1
Const ESB_DISABLE_RIGHT = &H2
Const ESB_DISABLE_UP = &H1
Const ESB_DISABLE_DOWN = &H2
Const ESB_DISABLE_LTUP = ESB_DISABLE_LEFT
Const ESB_DISABLE_RTDN = ESB_DISABLE_RIGHT
Declare Function SetProp Lib "user32" Alias "SetPropA" (ByVal hwnd As Long, ByVal lpString As String, ByVal hData As Long) As Long
Declare Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As Long, ByVal lpString As String) As Long
Declare Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As Long, ByVal lpString As String) As Long
Declare Function SetWindowText Lib "user32" Alias "SetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String) As Long
Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hwnd As Long) As Long
Declare Function GetClientRect Lib "user32" Alias "GetClientRect" (ByVal hwnd As Long, lpRect As RECT) As Long
Declare Function GetWindowRect Lib "user32" Alias "GetWindowRect" (ByVal hwnd As Long, lpRect As RECT) As Long
Declare Function AdjustWindowRect Lib "user32" Alias "AdjustWindowRect" (lpRect As RECT, ByVal dwStyle As Long, ByVal bMenu As Long) As Long
Declare Function AdjustWindowRectEx Lib "user32" Alias "AdjustWindowRectEx" (lpRect As RECT, ByVal dsStyle As Long, ByVal bMenu As Long, ByVal dwEsStyle As Long) As Long
' MessageBox() Flags
Const MB_OK = &H0&
Const MB_OKCANCEL = &H1&
Const MB_ABORTRETRYIGNORE = &H2&
Const MB_YESNOCANCEL = &H3&
Const MB_YESNO = &H4&
Const MB_RETRYCANCEL = &H5&
Const MB_ICONHAND = &H10&
Const MB_ICONQUESTION = &H20&
Const MB_ICONEXCLAMATION = &H30&
Const MB_ICONASTERISK = &H40&
Const MB_ICONINFORMATION = MB_ICONASTERISK
Const MB_ICONSTOP = MB_ICONHAND
Const MB_DEFBUTTON1 = &H0&
Const MB_DEFBUTTON2 = &H100&
Const MB_DEFBUTTON3 = &H200&
Const MB_APPLMODAL = &H0&
Const MB_SYSTEMMODAL = &H1000&
Const MB_TASKMODAL = &H2000&
Const MB_NOFOCUS = &H8000&
Const MB_SETFOREGROUND = &H10000
Const MB_DEFAULT_DESKTOP_ONLY = &H20000
Const MB_TYPEMASK = &HF&
Const MB_ICONMASK = &HF0&
Const MB_DEFMASK = &HF00&
Const MB_MODEMASK = &H3000&
Const MB_MISCMASK = &HC000&
Declare Function MessageBox Lib "user32" Alias "MessageBoxA" (ByVal hwnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As Long
Declare Function MessageBoxEx Lib "user32" Alias "MessageBoxExA" (ByVal hwnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal uType As Long, ByVal wLanguageId As Long) As Long
Declare Function MessageBeep Lib "user32" Alias "MessageBeep" (ByVal wType As Long) As Long
Declare Function ShowCursor Lib "user32" Alias "ShowCursor" (ByVal bShow As Long) As Long
Declare Function SetCursorPos Lib "user32" Alias "SetCursorPos" (ByVal x As Long, ByVal y As Long) As Long
Declare Function SetCursor Lib "user32" Alias "SetCursor" (ByVal hCursor As Long) As Long
Declare Function GetCursorPos Lib "user32" Alias "GetCursorPos" (lpPoint As POINTAPI) As Long
Declare Function ClipCursor Lib "user32" Alias "ClipCursor" (lpRect As Any) As Long
Declare Function GetCursor Lib "user32" Alias "GetCursor" () As Long
Declare Function GetClipCursor Lib "user32" Alias "GetClipCursor" (lprc As RECT) As Long
Declare Function CreateCaret Lib "user32" Alias "CreateCaret" (ByVal hwnd As Long, ByVal hBitmap As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Declare Function GetCaretBlinkTime Lib "user32" Alias "GetCaretBlinkTime" () As Long
Declare Function SetCaretBlinkTime Lib "user32" Alias "SetCaretBlinkTime" (ByVal wMSeconds As Long) As Long
Declare Function DestroyCaret Lib "user32" Alias "DestroyCaret" () As Long
Declare Function HideCaret Lib "user32" Alias "HideCaret" (ByVal hwnd As Long) As Long
Declare Function ShowCaret Lib "user32" Alias "ShowCaret" (ByVal hwnd As Long) As Long
Declare Function SetCaretPos Lib "user32" Alias "SetCaretPos" (ByVal x As Long, ByVal y As Long) As Long
Declare Function GetCaretPos Lib "user32" Alias "GetCaretPos" (lpPoint As POINTAPI) As Long
Declare Function ClientToScreen Lib "user32" Alias "ClientToScreen" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long
Declare Function ScreenToClient Lib "user32" Alias "ScreenToClient" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long
Declare Function MapWindowPoints Lib "user32" Alias "MapWindowPoints" (ByVal hwndFrom As Long, ByVal hwndTo As Long, lppt As Any, ByVal cPoints As Long) As Long
Declare Function WindowFromPoint Lib "user32" Alias "WindowFromPoint" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
Declare Function ChildWindowFromPoint Lib "user32" Alias "ChildWindowFromPoint" (ByVal hWnd As Long, ByVal xPoint As Long, ByVal yPoint As Long) As Long
' Color Types
Const CTLCOLOR_MSGBOX = 0
Const CTLCOLOR_EDIT = 1
Const CTLCOLOR_LISTBOX = 2
Const CTLCOLOR_BTN = 3
Const CTLCOLOR_DLG = 4
Const CTLCOLOR_SCROLLBAR = 5
Const CTLCOLOR_STATIC = 6
Const CTLCOLOR_MAX = 8 ' three bits max
Const COLOR_SCROLLBAR = 0
Const COLOR_BACKGROUND = 1
Const COLOR_ACTIVECAPTION = 2
Const COLOR_INACTIVECAPTION = 3
Const COLOR_MENU = 4
Const COLOR_WINDOW = 5
Const COLOR_WINDOWFRAME = 6
Const COLOR_MENUTEXT = 7
Const COLOR_WINDOWTEXT = 8
Const COLOR_CAPTIONTEXT = 9
Const COLOR_ACTIVEBORDER = 10
Const COLOR_INACTIVEBORDER = 11
Const COLOR_APPWORKSPACE = 12
Const COLOR_HIGHLIGHT = 13
Const COLOR_HIGHLIGHTTEXT = 14
Const COLOR_BTNFACE = 15
Const COLOR_BTNSHADOW = 16
Const COLOR_GRAYTEXT = 17
Const COLOR_BTNTEXT = 18
Const COLOR_INACTIVECAPTIONTEXT = 19
Const COLOR_BTNHIGHLIGHT = 20
Declare Function GetSysColor Lib "user32" Alias "GetSysColor" (ByVal nIndex As Long) As Long
Declare Function SetSysColors Lib "user32" Alias "SetSysColors" (ByVal nChanges As Long, lpSysColor As Long, lpColorValues As Long) As Long
Declare Function DrawFocusRect Lib "user32" Alias "DrawFocusRect" (ByVal hdc As Long, lpRect As RECT) As Long
Declare Function FillRect Lib "user32" Alias "FillRect" (ByVal hdc As Long, lpRect As RECT, ByVal hBrush As Long) As Long
Declare Function FrameRect Lib "user32" Alias "FrameRect" (ByVal hdc As Long, lpRect As RECT, ByVal hBrush As Long) As Long
Declare Function InvertRect Lib "user32" Alias "InvertRect" (ByVal hdc As Long, lpRect As RECT) As Long
Declare Function SetRect Lib "user32" Alias "SetRect" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function SetRectEmpty Lib "user32" Alias "SetRectEmpty" (lpRect As RECT) As Long
Declare Function CopyRect Lib "user32" Alias "CopyRect" (lpDestRect As RECT, lpSourceRect As RECT) As Long
Declare Function InflateRect Lib "user32" Alias "InflateRect" (lpRect As RECT, ByVal x As Long, ByVal y As Long) As Long
Declare Function IntersectRect Lib "user32" Alias "IntersectRect" (lpDestRect As RECT, lpSrc1Rect As RECT, lpSrc2Rect As RECT) As Long
Declare Function UnionRect Lib "user32" Alias "UnionRect" (lpDestRect As RECT, lpSrc1Rect As RECT, lpSrc2Rect As RECT) As Long
Declare Function SubtractRect Lib "user32" Alias "SubtractRect" (lprcDst As RECT, lprcSrc1 As RECT, lprcSrc2 As RECT) As Long
Declare Function OffsetRect Lib "user32" Alias "OffsetRect" (lpRect As RECT, ByVal x As Long, ByVal y As Long) As Long
Declare Function IsRectEmpty Lib "user32" Alias "IsRectEmpty" (lpRect As RECT) As Long
Declare Function EqualRect Lib "user32" Alias "EqualRect" (lpRect1 As RECT, lpRect2 As RECT) As Long
Declare Function PtInRect Lib "user32" Alias "PtInRect" (lpRect As RECT, pt As POINTAPI) As Long
Declare Function GetWindowWord Lib "user32" Alias "GetWindowWord" (ByVal hwnd As Long, ByVal nIndex As Long) As Integer
Declare Function SetWindowWord Lib "user32" Alias "SetWindowWord" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal wNewWord As Long) As Long
Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Declare Function GetClassWord Lib "user32" Alias "GetClassWord" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Declare Function SetClassWord Lib "user32" Alias "SetClassWord" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal wNewWord As Long) As Long
Declare Function GetClassLong Lib "user32" Alias "GetClassLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Declare Function SetClassLong Lib "user32" Alias "SetClassLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Declare Function GetDesktopWindow Lib "user32" Alias "GetDesktopWindow" () As Long
Declare Function GetParent Lib "user32" Alias "GetParent" (ByVal hwnd As Long) As Long
Declare Function SetParent Lib "user32" Alias "SetParent" (ByVal hWndChild As Long, ByVal hWndNewParent As Long) As Long
Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
Declare Function GetTopWindow Lib "user32" Alias "GetTopWindow" (ByVal hwnd As Long) As Long
Declare Function GetNextWindow Lib "user32" Alias "GetWindow" (ByVal hwnd As Long, ByVal wFlag As Long) As Long
Declare Function GetWindowThreadProcessId Lib "user32" Alias "GetWindowThreadProcessId" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
Declare Function GetLastActivePopup Lib "user32" Alias "GetLastActivePopup" (ByVal hwndOwnder As Long) As Long
' GetWindow() Constants
Const GW_HWNDFIRST = 0
Const GW_HWNDLAST = 1
Const GW_HWNDNEXT = 2
Const GW_HWNDPREV = 3
Const GW_OWNER = 4
Const GW_CHILD = 5
Const GW_MAX = 5
Declare Function GetWindow Lib "user32" Alias "GetWindow" (ByVal hwnd As Long, ByVal wCmd As Long) As Long
Declare Function UnhookWindowsHookEx Lib "user32" Alias "UnhookWindowsHookEx" (ByVal hHook As Long) As Long
Declare Function CallNextHookEx Lib "user32" Alias "CallNextHookEx" (ByVal hHook As Long, ByVal ncode As Long, ByVal wParam As Long, lParam As Any) As Long
' Menu flags for Add/Check/EnableMenuItem()
Const MF_INSERT = &H0&
Const MF_CHANGE = &H80&
Const MF_APPEND = &H100&
Const MF_DELETE = &H200&
Const MF_REMOVE = &H1000&
Const MF_BYCOMMAND = &H0&
Const MF_BYPOSITION = &H400&
Const MF_SEPARATOR = &H800&
Const MF_ENABLED = &H0&
Const MF_GRAYED = &H1&
Const MF_DISABLED = &H2&
Const MF_UNCHECKED = &H0&
Const MF_CHECKED = &H8&
Const MF_USECHECKBITMAPS = &H200&
Const MF_STRING = &H0&
Const MF_BITMAP = &H4&
Const MF_OWNERDRAW = &H100&
Const MF_POPUP = &H10&
Const MF_MENUBARBREAK = &H20&
Const MF_MENUBREAK = &H40&
Const MF_UNHILITE = &H0&
Const MF_HILITE = &H80&
Const MF_SYSMENU = &H2000&
Const MF_HELP = &H4000&
Const MF_MOUSESELECT = &H8000&
' Menu item resource format
Type MENUITEMTEMPLATEHEADER
versionNumber As Integer
offset As Integer
End Type
Type MENUITEMTEMPLATE
mtOption As Integer
mtID As Integer
mtString As Byte
End Type
Const MF_END = &H80
' System Menu Command Values
Const SC_SIZE = &HF000&
Const SC_MOVE = &HF010&
Const SC_MINIMIZE = &HF020&
Const SC_MAXIMIZE = &HF030&
Const SC_NEXTWINDOW = &HF040&
Const SC_PREVWINDOW = &HF050&
Const SC_CLOSE = &HF060&
Const SC_VSCROLL = &HF070&
Const SC_HSCROLL = &HF080&
Const SC_MOUSEMENU = &HF090&
Const SC_KEYMENU = &HF100&
Const SC_ARRANGE = &HF110&
Const SC_RESTORE = &HF120&
Const SC_TASKLIST = &HF130&
Const SC_SCREENSAVE = &HF140&
Const SC_HOTKEY = &HF150&
' Obsolete names
Const SC_ICON = SC_MINIMIZE
Const SC_ZOOM = SC_MAXIMIZE
' Resource Loading Routines
Declare Function LoadBitmap Lib "user32" Alias "LoadBitmapA" (ByVal hInstance As Long, ByVal lpBitmapName As String) As Long
Declare Function LoadCursor Lib "user32" Alias "LoadCursorA" (ByVal hInstance As Long, ByVal lpCursorName As String) As Long
Declare Function CreateCursor Lib "user32" Alias "CreateCursor" (ByVal hInstance As Long, ByVal nXhotspot As Long, ByVal nYhotspot As Long, ByVal nWidth As Long, ByVal nHeight As Long, lpANDbitPlane As Any, lpXORbitPlane As Any) As Long
Declare Function DestroyCursor Lib "user32" Alias "DestroyCursor" (ByVal hCursor As Long) As Long
Declare Function CopyCursor Lib "user32" Alias "CopyCursor" (ByVal hcur As Long) As Long
' Standard Cursor IDs
Const IDC_ARROW = 32512&
Const IDC_IBEAM = 32513&
Const IDC_WAIT = 32514&
Const IDC_CROSS = 32515&
Const IDC_UPARROW = 32516&
Const IDC_SIZE = 32640&
Const IDC_ICON = 32641&
Const IDC_SIZENWSE = 32642&
Const IDC_SIZENESW = 32643&
Const IDC_SIZEWE = 32644&
Const IDC_SIZENS = 32645&
Const IDC_SIZEALL = 32646&
Const IDC_NO = 32648&
Const IDC_APPSTARTING = 32650&
Type ICONINFO
fIcon As Long
xHotspot As Long
yHotspot As Long
hbmMask As Long
hbmColor As Long
End Type
Declare Function LoadIcon Lib "user32" Alias "LoadIconA" (ByVal hInstance As Long, ByVal lpIconName As String) As Long
Declare Function CreateIcon Lib "user32" Alias "CreateIcon" (ByVal hInstance As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal nPlanes As Byte, ByVal nBitsPixel As Byte, lpANDbits As Byte, lpXORbits As Byte) As Long
Declare Function DestroyIcon Lib "user32" Alias "DestroyIcon" (ByVal hIcon As Long) As Long
Declare Function LookupIconIdFromDirectory Lib "user32" Alias "LookupIconIdFromDirectory" (presbits As Byte, ByVal fIcon As Long) As Long
Declare Function CreateIconIndirect Lib "user32" Alias "CreateIconIndirect" (piconinfo As ICONINFO) As Long
Declare Function CopyIcon Lib "user32" Alias "CopyIcon" (ByVal hIcon As Long) As Long
Declare Function GetIconInfo Lib "user32" Alias "GetIconInfo" (ByVal hIcon As Long, piconinfo As ICONINFO) As Long
' OEM Resource Ordinal Numbers
Const OBM_CLOSE = 32754
Const OBM_UPARROW = 32753
Const OBM_DNARROW = 32752
Const OBM_RGARROW = 32751
Const OBM_LFARROW = 32750
Const OBM_REDUCE = 32749
Const OBM_ZOOM = 32748
Const OBM_RESTORE = 32747
Const OBM_REDUCED = 32746
Const OBM_ZOOMD = 32745
Const OBM_RESTORED = 32744
Const OBM_UPARROWD = 32743
Const OBM_DNARROWD = 32742
Const OBM_RGARROWD = 32741
Const OBM_LFARROWD = 32740
Const OBM_MNARROW = 32739
Const OBM_COMBO = 32738
Const OBM_UPARROWI = 32737
Const OBM_DNARROWI = 32736
Const OBM_RGARROWI = 32735
Const OBM_LFARROWI = 32734
Const OBM_OLD_CLOSE = 32767
Const OBM_SIZE = 32766
Const OBM_OLD_UPARROW = 32765
Const OBM_OLD_DNARROW = 32764
Const OBM_OLD_RGARROW = 32763
Const OBM_OLD_LFARROW = 32762
Const OBM_BTSIZE = 32761
Const OBM_CHECK = 32760
Const OBM_CHECKBOXES = 32759
Const OBM_BTNCORNERS = 32758
Const OBM_OLD_REDUCE = 32757
Const OBM_OLD_ZOOM = 32756
Const OBM_OLD_RESTORE = 32755
Const OCR_NORMAL = 32512
Const OCR_IBEAM = 32513
Const OCR_WAIT = 32514
Const OCR_CROSS = 32515
Const OCR_UP = 32516
Const OCR_SIZE = 32640
Const OCR_ICON = 32641
Const OCR_SIZENWSE = 32642
Const OCR_SIZENESW = 32643
Const OCR_SIZEWE = 32644
Const OCR_SIZENS = 32645
Const OCR_SIZEALL = 32646
Const OCR_ICOCUR = 32647
Const OCR_NO = 32648 ' not in win3.1
Const OIC_SAMPLE = 32512
Const OIC_HAND = 32513
Const OIC_QUES = 32514
Const OIC_BANG = 32515
Const OIC_NOTE = 32516
Const ORD_LANGDRIVER = 1 ' The ordinal number for the entry point of
' language drivers.
' Standard Icon IDs
Const IDI_APPLICATION = 32512&
Const IDI_HAND = 32513&
Const IDI_QUESTION = 32514&
Const IDI_EXCLAMATION = 32515&
Const IDI_ASTERISK = 32516&
Declare Function LoadString Lib "user32" Alias "LoadStringA" (ByVal hInstance As Long, ByVal wID As Long, ByVal lpBuffer As String, ByVal nBufferMax As Long) As Long
' Dialog Box Command IDs
Const IDOK = 1
Const IDCANCEL = 2
Const IDABORT = 3
Const IDRETRY = 4
Const IDIGNORE = 5
Const IDYES = 6
Const IDNO = 7
' Control Manager Structures and Definitions
' Edit Control Styles
Const ES_LEFT = &H0&
Const ES_CENTER = &H1&
Const ES_RIGHT = &H2&
Const ES_MULTILINE = &H4&
Const ES_UPPERCASE = &H8&
Const ES_LOWERCASE = &H10&
Const ES_PASSWORD = &H20&
Const ES_AUTOVSCROLL = &H40&
Const ES_AUTOHSCROLL = &H80&
Const ES_NOHIDESEL = &H100&
Const ES_OEMCONVERT = &H400&
Const ES_READONLY = &H800&
Const ES_WANTRETURN = &H1000&
' Edit Control Notification Codes
Const EN_SETFOCUS = &H100
Const EN_KILLFOCUS = &H200
Const EN_CHANGE = &H300
Const EN_UPDATE = &H400
Const EN_ERRSPACE = &H500
Const EN_MAXTEXT = &H501
Const EN_HSCROLL = &H601
Const EN_VSCROLL = &H602
' Edit Control Messages
Const EM_GETSEL = &HB0
Const EM_SETSEL = &HB1
Const EM_GETRECT = &HB2
Const EM_SETRECT = &HB3
Const EM_SETRECTNP = &HB4
Const EM_SCROLL = &HB5
Const EM_LINESCROLL = &HB6
Const EM_SCROLLCARET = &HB7
Const EM_GETMODIFY = &HB8
Const EM_SETMODIFY = &HB9
Const EM_GETLINECOUNT = &HBA
Const EM_LINEINDEX = &HBB
Const EM_SETHANDLE = &HBC
Const EM_GETHANDLE = &HBD
Const EM_GETTHUMB = &HBE
Const EM_LINELENGTH = &HC1
Const EM_REPLACESEL = &HC2
Const EM_GETLINE = &HC4
Const EM_LIMITTEXT = &HC5
Const EM_CANUNDO = &HC6
Const EM_UNDO = &HC7
Const EM_FMTLINES = &HC8
Const EM_LINEFROMCHAR = &HC9
Const EM_SETTABSTOPS = &HCB
Const EM_SETPASSWORDCHAR = &HCC
Const EM_EMPTYUNDOBUFFER = &HCD
Const EM_GETFIRSTVISIBLELINE = &HCE
Const EM_SETREADONLY = &HCF
Const EM_SETWORDBREAKPROC = &HD0
Const EM_GETWORDBREAKPROC = &HD1
Const EM_GETPASSWORDCHAR = &HD2
' EDITWORDBREAKPROC code values
Const WB_LEFT = 0
Const WB_RIGHT = 1
Const WB_ISDELIMITER = 2
' Button Control Styles
Const BS_PUSHBUTTON = &H0&
Const BS_DEFPUSHBUTTON = &H1&
Const BS_CHECKBOX = &H2&
Const BS_AUTOCHECKBOX = &H3&
Const BS_RADIOBUTTON = &H4&
Const BS_3STATE = &H5&
Const BS_AUTO3STATE = &H6&
Const BS_GROUPBOX = &H7&
Const BS_USERBUTTON = &H8&
Const BS_AUTORADIOBUTTON = &H9&
Const BS_OWNERDRAW = &HB&
Const BS_LEFTTEXT = &H20&
' User Button Notification Codes
Const BN_CLICKED = 0
Const BN_PAINT = 1
Const BN_HILITE = 2
Const BN_UNHILITE = 3
Const BN_DISABLE = 4
Const BN_DOUBLECLICKED = 5
' Button Control Messages
Const BM_GETCHECK = &HF0
Const BM_SETCHECK = &HF1
Const BM_GETSTATE = &HF2
Const BM_SETSTATE = &HF3
Const BM_SETSTYLE = &HF4
' Static Control Constants
Const SS_LEFT = &H0&
Const SS_CENTER = &H1&
Const SS_RIGHT = &H2&
Const SS_ICON = &H3&
Const SS_BLACKRECT = &H4&
Const SS_GRAYRECT = &H5&
Const SS_WHITERECT = &H6&
Const SS_BLACKFRAME = &H7&
Const SS_GRAYFRAME = &H8&
Const SS_WHITEFRAME = &H9&
Const SS_USERITEM = &HA&
Const SS_SIMPLE = &HB&
Const SS_LEFTNOWORDWRAP = &HC&
Const SS_NOPREFIX = &H80 ' Don't do "&" character translation
' Static Control Mesages
Const STM_SETICON = &H170
Const STM_GETICON = &H171
Const STM_MSGMAX = &H172
Const WC_DIALOG = 8002&
' Get/SetWindowWord/Long offsets for use with WC_DIALOG windows
Const DWL_MSGRESULT = 0
Const DWL_DLGPROC = 4
Const DWL_USER = 8
' Dialog Manager Routines
Declare Function IsDialogMessage Lib "user32" Alias "IsDialogMessageA" (ByVal hDlg As Long, lpMsg As MSG) As Long
Declare Function MapDialogRect Lib "user32" Alias "MapDialogRect" (ByVal hDlg As Long, lpRect As RECT) As Long
Declare Function DlgDirList Lib "user32" Alias "DlgDirListA" (ByVal hDlg As Long, ByVal lpPathSpec As String, ByVal nIDListBox As Long, ByVal nIDStaticPath As Long, ByVal wFileType As Long) As Long
' DlgDirList, DlgDirListComboBox flags values
Const DDL_READWRITE = &H0
Const DDL_READONLY = &H1
Const DDL_HIDDEN = &H2
Const DDL_SYSTEM = &H4
Const DDL_DIRECTORY = &H10
Const DDL_ARCHIVE = &H20
Const DDL_POSTMSGS = &H2000
Const DDL_DRIVES = &H4000
Const DDL_EXCLUSIVE = &H8000
Declare Function DlgDirSelectEx Lib "user32" Alias "DlgDirSelectExA" (ByVal hWndDlg As Long, ByVal lpszPath As String, ByVal cbPath As Long, ByVal idListBox As Long) As Long
Declare Function DlgDirListComboBox Lib "user32" Alias "DlgDirListComboBoxA" (ByVal hDlg As Long, ByVal lpPathSpec As String, ByVal nIDComboBox As Long, ByVal nIDStaticPath As Long, ByVal wFileType As Long) As Long
Declare Function DlgDirSelectComboBoxEx Lib "user32" Alias "DlgDirSelectComboBoxExA" (ByVal hWndDlg As Long, ByVal lpszPath As String, ByVal cbPath As Long, ByVal idComboBox As Long) As Long
' Dialog Styles
Const DS_ABSALIGN = &H1&
Const DS_SYSMODAL = &H2&
Const DS_LOCALEDIT = &H20 ' Edit items get Local storage.
Const DS_SETFONT = &H40 ' User specified font for Dlg controls
Const DS_MODALFRAME = &H80 ' Can be combined with WS_CAPTION
Const DS_NOIDLEMSG = &H100 ' WM_ENTERIDLE message will not be sent
Const DS_SETFOREGROUND = &H200 ' not in win3.1
Const DM_GETDEFID = WM_USER + 0
Const DM_SETDEFID = WM_USER + 1
Const DC_HASDEFID = &H534 '0x534B
' Dialog Codes
Const DLGC_WANTARROWS = &H1 ' Control wants arrow keys
Const DLGC_WANTTAB = &H2 ' Control wants tab keys
Const DLGC_WANTALLKEYS = &H4 ' Control wants all keys
Const DLGC_WANTMESSAGE = &H4 ' Pass message to control
Const DLGC_STATIC = &H100 ' Static item: don't include
Const DLGC_BUTTON = &H2000 ' Button item: can be checked
Const LB_CTLCODE = 0&
' Listbox Return Values
Const LB_OKAY = 0
Const LB_ERR = (-1)
Const LB_ERRSPACE = (-2)
' The idStaticPath parameter to DlgDirList can have the following values
' ORed if the list box should show other details of the files along with
' the name of the files;
' all other details also will be returned
' Listbox Notification Codes
Const LBN_ERRSPACE = (-2)
Const LBN_SELCHANGE = 1
Const LBN_DBLCLK = 2
Const LBN_SELCANCEL = 3
Const LBN_SETFOCUS = 4
Const LBN_KILLFOCUS = 5
' Listbox messages
Const LB_ADDSTRING = &H180
Const LB_INSERTSTRING = &H181
Const LB_DELETESTRING = &H182
Const LB_SELITEMRANGEEX = &H183
Const LB_RESETCONTENT = &H184
Const LB_SETSEL = &H185
Const LB_SETCURSEL = &H186
Const LB_GETSEL = &H187
Const LB_GETCURSEL = &H188
Const LB_GETTEXT = &H189
Const LB_GETTEXTLEN = &H18A
Const LB_GETCOUNT = &H18B
Const LB_SELECTSTRING = &H18C
Const LB_DIR = &H18D
Const LB_GETTOPINDEX = &H18E
Const LB_FINDSTRING = &H18F
Const LB_GETSELCOUNT = &H190
Const LB_GETSELITEMS = &H191
Const LB_SETTABSTOPS = &H192
Const LB_GETHORIZONTALEXTENT = &H193
Const LB_SETHORIZONTALEXTENT = &H194
Const LB_SETCOLUMNWIDTH = &H195
Const LB_ADDFILE = &H196
Const LB_SETTOPINDEX = &H197
Const LB_GETITEMRECT = &H198
Const LB_GETITEMDATA = &H199
Const LB_SETITEMDATA = &H19A
Const LB_SELITEMRANGE = &H19B
Const LB_SETANCHORINDEX = &H19C
Const LB_GETANCHORINDEX = &H19D
Const LB_SETCARETINDEX = &H19E
Const LB_GETCARETINDEX = &H19F
Const LB_SETITEMHEIGHT = &H1A0
Const LB_GETITEMHEIGHT = &H1A1
Const LB_FINDSTRINGEXACT = &H1A2
Const LB_SETLOCALE = &H1A5
Const LB_GETLOCALE = &H1A6
Const LB_SETCOUNT = &H1A7
Const LB_MSGMAX = &H1A8
' Listbox Styles
Const LBS_NOTIFY = &H1&
Const LBS_SORT = &H2&
Const LBS_NOREDRAW = &H4&
Const LBS_MULTIPLESEL = &H8&
Const LBS_OWNERDRAWFIXED = &H10&
Const LBS_OWNERDRAWVARIABLE = &H20&
Const LBS_HASSTRINGS = &H40&
Const LBS_USETABSTOPS = &H80&
Const LBS_NOINTEGRALHEIGHT = &H100&
Const LBS_MULTICOLUMN = &H200&
Const LBS_WANTKEYBOARDINPUT = &H400&
Const LBS_EXTENDEDSEL = &H800&
Const LBS_DISABLENOSCROLL = &H1000&
Const LBS_NODATA = &H2000&
Const LBS_STANDARD = (LBS_NOTIFY Or LBS_SORT Or WS_VSCROLL Or WS_BORDER)
' Combo Box return Values
Const CB_OKAY = 0
Const CB_ERR = (-1)
Const CB_ERRSPACE = (-2)
' Combo Box Notification Codes
Const CBN_ERRSPACE = (-1)
Const CBN_SELCHANGE = 1
Const CBN_DBLCLK = 2
Const CBN_SETFOCUS = 3
Const CBN_KILLFOCUS = 4
Const CBN_EDITCHANGE = 5
Const CBN_EDITUPDATE = 6
Const CBN_DROPDOWN = 7
Const CBN_CLOSEUP = 8
Const CBN_SELENDOK = 9
Const CBN_SELENDCANCEL = 10
' Combo Box styles
Const CBS_SIMPLE = &H1&
Const CBS_DROPDOWN = &H2&
Const CBS_DROPDOWNLIST = &H3&
Const CBS_OWNERDRAWFIXED = &H10&
Const CBS_OWNERDRAWVARIABLE = &H20&
Const CBS_AUTOHSCROLL = &H40&
Const CBS_OEMCONVERT = &H80&
Const CBS_SORT = &H100&
Const CBS_HASSTRINGS = &H200&
Const CBS_NOINTEGRALHEIGHT = &H400&
Const CBS_DISABLENOSCROLL = &H800&
' Combo Box messages
Const CB_GETEDITSEL = &H140
Const CB_LIMITTEXT = &H141
Const CB_SETEDITSEL = &H142
Const CB_ADDSTRING = &H143
Const CB_DELETESTRING = &H144
Const CB_DIR = &H145
Const CB_GETCOUNT = &H146
Const CB_GETCURSEL = &H147
Const CB_GETLBTEXT = &H148
Const CB_GETLBTEXTLEN = &H149
Const CB_INSERTSTRING = &H14A
Const CB_RESETCONTENT = &H14B
Const CB_FINDSTRING = &H14C
Const CB_SELECTSTRING = &H14D
Const CB_SETCURSEL = &H14E
Const CB_SHOWDROPDOWN = &H14F
Const CB_GETITEMDATA = &H150
Const CB_SETITEMDATA = &H151
Const CB_GETDROPPEDCONTROLRECT = &H152
Const CB_SETITEMHEIGHT = &H153
Const CB_GETITEMHEIGHT = &H154
Const CB_SETEXTENDEDUI = &H155
Const CB_GETEXTENDEDUI = &H156
Const CB_GETDROPPEDSTATE = &H157
Const CB_FINDSTRINGEXACT = &H158
Const CB_SETLOCALE = &H159
Const CB_GETLOCALE = &H15A
Const CB_MSGMAX = &H15B
' Scroll Bar Styles
Const SBS_HORZ = &H0&
Const SBS_VERT = &H1&
Const SBS_TOPALIGN = &H2&
Const SBS_LEFTALIGN = &H2&
Const SBS_BOTTOMALIGN = &H4&
Const SBS_RIGHTALIGN = &H4&
Const SBS_SIZEBOXTOPLEFTALIGN = &H2&
Const SBS_SIZEBOXBOTTOMRIGHTALIGN = &H4&
Const SBS_SIZEBOX = &H8&
' Scroll bar messages
Const SBM_SETPOS = &HE0 ' not in win3.1
Const SBM_GETPOS = &HE1 ' not in win3.1
Const SBM_SETRANGE = &HE2 ' not in win3.1
Const SBM_SETRANGEREDRAW = &HE6 ' not in win3.1
Const SBM_GETRANGE = &HE3 ' not in win3.1
Const SBM_ENABLE_ARROWS = &HE4 ' not in win3.1
Const MDIS_ALLCHILDSTYLES = &H1
' wParam values for WM_MDITILE and WM_MDICASCADE messages.
Const MDITILE_VERTICAL = &H0
Const MDITILE_HORIZONTAL = &H1
Const MDITILE_SKIPDISABLED = &H2
Type MDICREATESTRUCT
szClass As String
szTitle As String
hOwner As Long
x As Long
y As Long
cx As Long
cy As Long
style As Long
lParam As Long
End Type
Type CLIENTCREATESTRUCT
hWindowMenu As Long
idFirstChild As Long
End Type
Declare Function DefFrameProc Lib "user32" Alias "DefFrameProcA" (ByVal hwnd As Long, ByVal hWndMDIClient As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function DefMDIChildProc Lib "user32" Alias "DefMDIChildProcA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function TranslateMDISysAccel Lib "user32" Alias "TranslateMDISysAccel" (ByVal hWndClient As Long, lpMsg As MSG) As Long
Declare Function ArrangeIconicWindows Lib "user32" Alias "ArrangeIconicWindows" (ByVal hwnd As Long) As Long
Declare Function CreateMDIWindow Lib "user32" Alias "CreateMDIWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String, ByVal dwStyle As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hWndParent As Long, ByVal hInstance As Long, ByVal lParam As Long) As Long
' Help engine section.
Type MULTIKEYHELP
mkSize As Long
mkKeylist As Byte
szKeyphrase As String * 253 ' Array length is arbitrary; may be changed
End Type
Type HELPWININFO
wStructSize As Long
x As Long
y As Long
dx As Long
dy As Long
wMax As Long
rgchMember As String * 2
End Type
' Commands to pass WinHelp()
Const HELP_CONTEXT = &H1 ' Display topic in ulTopic
Const HELP_QUIT = &H2 ' Terminate help
Const HELP_INDEX = &H3 ' Display index
Const HELP_CONTENTS = &H3&
Const HELP_HELPONHELP = &H4 ' Display help on using help
Const HELP_SETINDEX = &H5 ' Set current Index for multi index help
Const HELP_SETCONTENTS = &H5&
Const HELP_CONTEXTPOPUP = &H8&
Const HELP_FORCEFILE = &H9&
Const HELP_KEY = &H101 ' Display topic for keyword in offabData
Const HELP_COMMAND = &H102&
Const HELP_PARTIALKEY = &H105&
Const HELP_MULTIKEY = &H201&
Const HELP_SETWINPOS = &H203&
Declare Function WinHelp Lib "user32" Alias "WinHelpA" (ByVal hwnd As Long, ByVal lpHelpFile As String, ByVal wCommand As Long, ByVal dwData As Long) As Long
' Parameter for SystemParametersInfo()
Const SPI_GETBEEP = 1
Const SPI_SETBEEP = 2
Const SPI_GETMOUSE = 3
Const SPI_SETMOUSE = 4
Const SPI_GETBORDER = 5
Const SPI_SETBORDER = 6
Const SPI_GETKEYBOARDSPEED = 10
Const SPI_SETKEYBOARDSPEED = 11
Const SPI_LANGDRIVER = 12
Const SPI_ICONHORIZONTALSPACING = 13
Const SPI_GETSCREENSAVETIMEOUT = 14
Const SPI_SETSCREENSAVETIMEOUT = 15
Const SPI_GETSCREENSAVEACTIVE = 16
Const SPI_SETSCREENSAVEACTIVE = 17
Const SPI_GETGRIDGRANULARITY = 18
Const SPI_SETGRIDGRANULARITY = 19
Const SPI_SETDESKWALLPAPER = 20
Const SPI_SETDESKPATTERN = 21
Const SPI_GETKEYBOARDDELAY = 22
Const SPI_SETKEYBOARDDELAY = 23
Const SPI_ICONVERTICALSPACING = 24
Const SPI_GETICONTITLEWRAP = 25
Const SPI_SETICONTITLEWRAP = 26
Const SPI_GETMENUDROPALIGNMENT = 27
Const SPI_SETMENUDROPALIGNMENT = 28
Const SPI_SETDOUBLECLKWIDTH = 29
Const SPI_SETDOUBLECLKHEIGHT = 30
Const SPI_GETICONTITLELOGFONT = 31
Const SPI_SETDOUBLECLICKTIME = 32
Const SPI_SETMOUSEBUTTONSWAP = 33
Const SPI_SETICONTITLELOGFONT = 34
Const SPI_GETFASTTASKSWITCH = 35
Const SPI_SETFASTTASKSWITCH = 36
Const SPI_SETDRAGFULLWINDOWS = 37
Const SPI_GETDRAGFULLWINDOWS = 38
Const SPI_GETNONCLIENTMETRICS = 41
Const SPI_SETNONCLIENTMETRICS = 42
Const SPI_GETMINIMIZEDMETRICS = 43
Const SPI_SETMINIMIZEDMETRICS = 44
Const SPI_GETICONMETRICS = 45
Const SPI_SETICONMETRICS = 46
Const SPI_SETWORKAREA = 47
Const SPI_GETWORKAREA = 48
Const SPI_SETPENWINDOWS = 49
Const SPI_GETFILTERKEYS = 50
Const SPI_SETFILTERKEYS = 51
Const SPI_GETTOGGLEKEYS = 52
Const SPI_SETTOGGLEKEYS = 53
Const SPI_GETMOUSEKEYS = 54
Const SPI_SETMOUSEKEYS = 55
Const SPI_GETSHOWSOUNDS = 56
Const SPI_SETSHOWSOUNDS = 57
Const SPI_GETSTICKYKEYS = 58
Const SPI_SETSTICKYKEYS = 59
Const SPI_GETACCESSTIMEOUT = 60
Const SPI_SETACCESSTIMEOUT = 61
Const SPI_GETSERIALKEYS = 62
Const SPI_SETSERIALKEYS = 63
Const SPI_GETSOUNDSENTRY = 64
Const SPI_SETSOUNDSENTRY = 65
Const SPI_GETHIGHCONTRAST = 66
Const SPI_SETHIGHCONTRAST = 67
Const SPI_GETKEYBOARDPREF = 68
Const SPI_SETKEYBOARDPREF = 69
Const SPI_GETSCREENREADER = 70
Const SPI_SETSCREENREADER = 71
Const SPI_GETANIMATION = 72
Const SPI_SETANIMATION = 73
Const SPI_GETFONTSMOOTHING = 74
Const SPI_SETFONTSMOOTHING = 75
Const SPI_SETDRAGWIDTH = 76
Const SPI_SETDRAGHEIGHT = 77
Const SPI_SETHANDHELD = 78
Const SPI_GETLOWPOWERTIMEOUT = 79
Const SPI_GETPOWEROFFTIMEOUT = 80
Const SPI_SETLOWPOWERTIMEOUT = 81
Const SPI_SETPOWEROFFTIMEOUT = 82
Const SPI_GETLOWPOWERACTIVE = 83
Const SPI_GETPOWEROFFACTIVE = 84
Const SPI_SETLOWPOWERACTIVE = 85
Const SPI_SETPOWEROFFACTIVE = 86
Const SPI_SETCURSORS = 87
Const SPI_SETICONS = 88
Const SPI_GETDEFAULTINPUTLANG = 89
Const SPI_SETDEFAULTINPUTLANG = 90
Const SPI_SETLANGTOGGLE = 91
Const SPI_GETWINDOWSEXTENSION = 92
Const SPI_SETMOUSETRAILS = 93
Const SPI_GETMOUSETRAILS = 94
Const SPI_SCREENSAVERRUNNING = 97
' SystemParametersInfo flags
Const SPIF_UPDATEINIFILE = &H1
Const SPIF_SENDWININICHANGE = &H2
Declare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Long, ByVal uParam As Long, ByRef lpvParam As Any, ByVal fuWinIni As Long) As Long
Declare Function DdeSetQualityOfService Lib "user32" Alias "DdeSetQualityOfService" (ByVal hWndClient As Long, pqosNew As SECURITY_QUALITY_OF_SERVICE, pqosPrev As SECURITY_QUALITY_OF_SERVICE) As Long
Declare Function ImpersonateDdeClientWindow Lib "user32" Alias "ImpersonateDdeClientWindow" (ByVal hWndClient As Long, ByVal hWndServer As Long) As Long
Declare Function PackDDElParam Lib "user32" Alias "PackDDElParam" (ByVal msg As Long, ByVal uiLo As Long, ByVal uiHi As Long) As Long
Declare Function UnpackDDElParam Lib "user32" Alias "UnpackDDElParam" (ByVal msg As Long, ByVal lParam As Long, puiLo As Long, puiHi As Long) As Long
Declare Function FreeDDElParam Lib "user32" Alias "FreeDDElParam" (ByVal msg As Long, ByVal lParam As Long) As Long
Declare Function ReuseDDElParam Lib "user32" Alias "ReuseDDElParam" (ByVal lParam As Long, ByVal msgIn As Long, ByVal msgOut As Long, ByVal uiLo As Long, ByVal uiHi As Long) As Long
Type HSZPAIR
hszSvc As Long
hszTopic As Long
End Type
'//
'// Quality Of Service
'//
Type SECURITY_QUALITY_OF_SERVICE
Length As Long
Impersonationlevel As Integer
ContextTrackingMode As Integer
EffectiveOnly As Long
End Type
Type CONVCONTEXT
cb As Long
wFlags As Long
wCountryID As Long
iCodePage As Long
dwLangID As Long
dwSecurity As Long
qos As SECURITY_QUALITY_OF_SERVICE
End Type
Type CONVINFO
cb As Long
hUser As Long
hConvPartner As Long
hszSvcPartner As Long
hszServiceReq As Long
hszTopic As Long
hszItem As Long
wFmt As Long
wType As Long
wStatus As Long
wConvst As Long
wLastError As Long
hConvList As Long
ConvCtxt As CONVCONTEXT
hwnd As Long
hwndPartner As Long
End Type
' conversation states (usState)
Const XST_NULL = 0 ' quiescent states
Const XST_INCOMPLETE = 1
Const XST_CONNECTED = 2
Const XST_INIT1 = 3 ' mid-initiation states
Const XST_INIT2 = 4
Const XST_REQSENT = 5 ' active conversation states
Const XST_DATARCVD = 6
Const XST_POKESENT = 7
Const XST_POKEACKRCVD = 8
Const XST_EXECSENT = 9
Const XST_EXECACKRCVD = 10
Const XST_ADVSENT = 11
Const XST_UNADVSENT = 12
Const XST_ADVACKRCVD = 13
Const XST_UNADVACKRCVD = 14
Const XST_ADVDATASENT = 15
Const XST_ADVDATAACKRCVD = 16
' used in LOWORD(dwData1) of XTYP_ADVREQ callbacks...
Const CADV_LATEACK = &HFFFF
' conversation status bits (fsStatus)
Const ST_CONNECTED = &H1
Const ST_ADVISE = &H2
Const ST_ISLOCAL = &H4
Const ST_BLOCKED = &H8
Const ST_CLIENT = &H10
Const ST_TERMINATED = &H20
Const ST_INLIST = &H40
Const ST_BLOCKNEXT = &H80
Const ST_ISSELF = &H100
' DDE constants for wStatus field
Const DDE_FACK = &H8000
Const DDE_FBUSY = &H4000
Const DDE_FDEFERUPD = &H4000
Const DDE_FACKREQ = &H8000
Const DDE_FRELEASE = &H2000
Const DDE_FREQUESTED = &H1000
Const DDE_FAPPSTATUS = &HFF
Const DDE_FNOTPROCESSED = &H0
Const DDE_FACKRESERVED = (Not (DDE_FACK Or DDE_FBUSY Or DDE_FAPPSTATUS))
Const DDE_FADVRESERVED = (Not (DDE_FACKREQ Or DDE_FDEFERUPD))
Const DDE_FDATRESERVED = (Not (DDE_FACKREQ Or DDE_FRELEASE Or DDE_FREQUESTED))
Const DDE_FPOKRESERVED = (Not (DDE_FRELEASE))
' message filter hook types
Const MSGF_DDEMGR = &H8001
' codepage constants
Const CP_WINANSI = 1004 ' default codepage for windows old DDE convs.
Const CP_WINUNICODE = 1200
' transaction types
Const XTYPF_NOBLOCK = &H2 ' CBR_BLOCK will not work
Const XTYPF_NODATA = &H4 ' DDE_FDEFERUPD
Const XTYPF_ACKREQ = &H8 ' DDE_FACKREQ
Const XCLASS_MASK = &HFC00
Const XCLASS_BOOL = &H1000
Const XCLASS_DATA = &H2000
Const XCLASS_FLAGS = &H4000
Const XCLASS_NOTIFICATION = &H8000
Const XTYP_ERROR = (&H0 Or XCLASS_NOTIFICATION Or XTYPF_NOBLOCK)
Const XTYP_ADVDATA = (&H10 Or XCLASS_FLAGS)
Const XTYP_ADVREQ = (&H20 Or XCLASS_DATA Or XTYPF_NOBLOCK)
Const XTYP_ADVSTART = (&H30 Or XCLASS_BOOL)
Const XTYP_ADVSTOP = (&H40 Or XCLASS_NOTIFICATION)
Const XTYP_EXECUTE = (&H50 Or XCLASS_FLAGS)
Const XTYP_CONNECT = (&H60 Or XCLASS_BOOL Or XTYPF_NOBLOCK)
Const XTYP_CONNECT_CONFIRM = (&H70 Or XCLASS_NOTIFICATION Or XTYPF_NOBLOCK)
Const XTYP_XACT_COMPLETE = (&H80 Or XCLASS_NOTIFICATION)
Const XTYP_POKE = (&H90 Or XCLASS_FLAGS)
Const XTYP_REGISTER = (&HA0 Or XCLASS_NOTIFICATION Or XTYPF_NOBLOCK)
Const XTYP_REQUEST = (&HB0 Or XCLASS_DATA)
Const XTYP_DISCONNECT = (&HC0 Or XCLASS_NOTIFICATION Or XTYPF_NOBLOCK)
Const XTYP_UNREGISTER = (&HD0 Or XCLASS_NOTIFICATION Or XTYPF_NOBLOCK)
Const XTYP_WILDCONNECT = (&HE0 Or XCLASS_DATA Or XTYPF_NOBLOCK)
Const XTYP_MASK = &HF0
Const XTYP_SHIFT = 4 ' shift to turn XTYP_ into an index
' Timeout constants
Const TIMEOUT_ASYNC = &HFFFF
' Transaction ID constants
Const QID_SYNC = &HFFFF
' Public strings used in DDE
Const SZDDESYS_TOPIC = "System"
Const SZDDESYS_ITEM_TOPICS = "Topics"
Const SZDDESYS_ITEM_SYSITEMS = "SysItems"
Const SZDDESYS_ITEM_RTNMSG = "ReturnMessage"
Const SZDDESYS_ITEM_STATUS = "Status"
Const SZDDESYS_ITEM_FORMATS = "Formats"
Const SZDDESYS_ITEM_HELP = "Help"
Const SZDDE_ITEM_ITEMLIST = "TopicItemList"
Const CBR_BLOCK = &HFFFF
' Callback filter flags for use with standard apps.
Const CBF_FAIL_SELFCONNECTIONS = &H1000
Const CBF_FAIL_CONNECTIONS = &H2000
Const CBF_FAIL_ADVISES = &H4000
Const CBF_FAIL_EXECUTES = &H8000
Const CBF_FAIL_POKES = &H10000
Const CBF_FAIL_REQUESTS = &H20000
Const CBF_FAIL_ALLSVRXACTIONS = &H3F000
Const CBF_SKIP_CONNECT_CONFIRMS = &H40000
Const CBF_SKIP_REGISTRATIONS = &H80000
Const CBF_SKIP_UNREGISTRATIONS = &H100000
Const CBF_SKIP_DISCONNECTS = &H200000
Const CBF_SKIP_ALLNOTIFICATIONS = &H3C0000
' Application command flags
Const APPCMD_CLIENTONLY = &H10&
Const APPCMD_FILTERINITS = &H20&
Const APPCMD_MASK = &HFF0&
' Application classification flags
Const APPCLASS_STANDARD = &H0&
Const APPCLASS_MASK = &HF&
Declare Function DdeUninitialize Lib "user32" Alias "DdeUninitialize" (ByVal idInst As Long) As Long
' conversation enumeration functions
Declare Function DdeConnectList Lib "user32" Alias "DdeConnectList" (ByVal idInst As Long, ByVal hszService As Long, ByVal hszTopic As Long, ByVal hConvList As Long, pCC As CONVCONTEXT) As Long
Declare Function DdeQueryNextServer Lib "user32" Alias "DdeQueryNextServer" (ByVal hConvList As Long, ByVal hConvPrev As Long) As Long
Declare Function DdeDisconnectList Lib "user32" Alias "DdeDisconnectList" (ByVal hConvList As Long) As Long
' conversation control functions
Declare Function DdeConnect Lib "user32" Alias "DdeConnect" (ByVal idInst As Long, ByVal hszService As Long, ByVal hszTopic As Long, pCC As CONVCONTEXT) As Long
Declare Function DdeDisconnect Lib "user32" Alias "DdeDisconnect" (ByVal hConv As Long) As Long
Declare Function DdeReconnect Lib "user32" Alias "DdeReconnect" (ByVal hConv As Long) As Long
Declare Function DdeQueryConvInfo Lib "user32" Alias "DdeQueryConvInfo" (ByVal hConv As Long, ByVal idTransaction As Long, pConvInfo As CONVINFO) As Long
Declare Function DdeSetUserHandle Lib "user32" Alias "DdeSetUserHandle" (ByVal hConv As Long, ByVal id As Long, ByVal hUser As Long) As Long
Declare Function DdeAbandonTransaction Lib "user32" Alias "DdeAbandonTransaction" (ByVal idInst As Long, ByVal hConv As Long, ByVal idTransaction As Long) As Long
' app server interface functions
Declare Function DdePostAdvise Lib "user32" Alias "DdePostAdvise" (ByVal idInst As Long, ByVal hszTopic As Long, ByVal hszItem As Long) As Long
Declare Function DdeEnableCallback Lib "user32" Alias "DdeEnableCallback" (ByVal idInst As Long, ByVal hConv As Long, ByVal wCmd As Long) As Long
Declare Function DdeImpersonateClient Lib "user32" Alias "DdeImpersonateClient" (ByVal hConv As Long) As Long
Const EC_ENABLEALL = 0
Const EC_ENABLEONE = ST_BLOCKNEXT
Const EC_DISABLE = ST_BLOCKED
Const EC_QUERYWAITING = 2
Declare Function DdeNameService Lib "user32" Alias "DdeNameService" (ByVal idInst As Long, ByVal hsz1 As Long, ByVal hsz2 As Long, ByVal afCmd As Long) As Long
Const DNS_REGISTER = &H1
Const DNS_UNREGISTER = &H2
Const DNS_FILTERON = &H4
Const DNS_FILTEROFF = &H8
' app client interface functions
Declare Function DdeClientTransaction Lib "user32" Alias "DdeClientTransaction" (pData As Byte, ByVal cbData As Long, ByVal hConv As Long, ByVal hszItem As Long, ByVal wFmt As Long, ByVal wType As Long, ByVal dwTimeout As Long, pdwResult As Long) As Long
' data transfer functions
Declare Function DdeCreateDataHandle Lib "user32" Alias "DdeCreateDataHandle" (ByVal idInst As Long, pSrc As Byte, ByVal cb As Long, ByVal cbOff As Long, ByVal hszItem As Long, ByVal wFmt As Long, ByVal afCmd As Long) As Long
Declare Function DdeAddData Lib "user32" Alias "DdeAddDataA" (ByVal hData As Long, pSrc As Byte, ByVal cb As Long, ByVal cbOff As Long) As Long
Declare Function DdeGetData Lib "user32" Alias "DdeGetDataA" (ByVal hData As Long, pDst As Byte, ByVal cbMax As Long, ByVal cbOff As Long) As Long
Declare Function DdeAccessData Lib "user32" Alias "DdeAccessDataA" (ByVal hData As Long, pcbDataSize As Long) As Long
Declare Function DdeUnaccessData Lib "user32" Alias "DdeUnaccessDataA" (ByVal hData As Long) As Long
Declare Function DdeFreeDataHandle Lib "user32" Alias "DdeFreeDataHandle" (ByVal hData As Long) As Long
Const HDATA_APPOWNED = &H1
Declare Function DdeGetLastError Lib "user32" Alias "DdeGetLastError" (ByVal idInst As Long) As Long
Const DMLERR_NO_ERROR = 0 ' must be 0
Const DMLERR_FIRST = &H4000
Const DMLERR_ADVACKTIMEOUT = &H4000
Const DMLERR_BUSY = &H4001
Const DMLERR_DATAACKTIMEOUT = &H4002
Const DMLERR_DLL_NOT_INITIALIZED = &H4003
Const DMLERR_DLL_USAGE = &H4004
Const DMLERR_EXECACKTIMEOUT = &H4005
Const DMLERR_INVALIDPARAMETER = &H4006
Const DMLERR_LOW_MEMORY = &H4007
Const DMLERR_MEMORY_ERROR = &H4008
Const DMLERR_NOTPROCESSED = &H4009
Const DMLERR_NO_CONV_ESTABLISHED = &H400A
Const DMLERR_POKEACKTIMEOUT = &H400B
Const DMLERR_POSTMSG_FAILED = &H400C
Const DMLERR_REENTRANCY = &H400D
Const DMLERR_SERVER_DIED = &H400E
Const DMLERR_SYS_ERROR = &H400F
Const DMLERR_UNADVACKTIMEOUT = &H4010
Const DMLERR_UNFOUND_QUEUE_ID = &H4011
Const DMLERR_LAST = &H4011
Declare Function DdeCreateStringHandle Lib "user32" Alias "DdeCreateStringHandleA" (ByVal idInst As Long, ByVal psz As String, ByVal iCodePage As Long) As Long
Declare Function DdeQueryString Lib "user32" Alias "DdeQueryStringA" (ByVal idInst As Long, ByVal hsz As Long, ByVal psz As String, ByVal cchMax As Long, ByVal iCodePage As Long) As Long
Declare Function DdeFreeStringHandle Lib "user32" Alias "DdeFreeStringHandle" (ByVal idInst As Long, ByVal hsz As Long) As Long
Declare Function DdeKeepStringHandle Lib "user32" Alias "DdeKeepStringHandle" (ByVal idInst As Long, ByVal hsz As Long) As Long
Declare Function DdeCmpStringHandles Lib "user32" Alias "DdeCmpStringHandles" (ByVal hsz1 As Long, ByVal hsz2 As Long) As Long
Type DDEML_MSG_HOOK_DATA ' new for NT
uiLo As Long ' unpacked lo and hi parts of lParam
uiHi As Long
cbData As Long ' amount of data in message, if any. May be > than 32 bytes.
Data(8) As Long ' data peeking by DDESPY is limited to 32 bytes.
End Type
Type MONMSGSTRUCT
cb As Long
hwndTo As Long
dwTime As Long
htask As Long
wMsg As Long
wParam As Long
lParam As Long
dmhd As DDEML_MSG_HOOK_DATA ' new for NT
End Type
Type MONCBSTRUCT
cb As Long
dwTime As Long
htask As Long
dwRet As Long
wType As Long
wFmt As Long
hConv As Long
hsz1 As Long
hsz2 As Long
hData As Long
dwData1 As Long
dwData2 As Long
cc As CONVCONTEXT ' new for NT for XTYP_CONNECT callbacks
cbData As Long ' new for NT for data peeking
Data(8) As Long ' new for NT for data peeking
End Type
Type MONHSZSTRUCT
cb As Long
fsAction As Long ' MH_ value
dwTime As Long
hsz As Long
htask As Long
str As Byte
End Type
Const MH_CREATE = 1
Const MH_KEEP = 2
Const MH_DELETE = 3
Const MH_CLEANUP = 4
Type MONERRSTRUCT
cb As Long
wLastError As Long
dwTime As Long
htask As Long
End Type
Type MONLINKSTRUCT
cb As Long
dwTime As Long
htask As Long
fEstablished As Long
fNoData As Long
hszSvc As Long
hszTopic As Long
hszItem As Long
wFmt As Long
fServer As Long
hConvServer As Long
hConvClient As Long
End Type
Type MONCONVSTRUCT
cb As Long
fConnect As Long
dwTime As Long
htask As Long
hszSvc As Long
hszTopic As Long
hConvClient As Long ' Globally unique value != apps local hConv
hConvServer As Long ' Globally unique value != apps local hConv
End Type
Const MAX_MONITORS = 4
Const APPCLASS_MONITOR = &H1&
Const XTYP_MONITOR = (&HF0 Or XCLASS_NOTIFICATION Or XTYPF_NOBLOCK)
' Callback filter flags for use with MONITOR apps - 0 implies no monitor callbacks
Const MF_HSZ_INFO = &H1000000
Const MF_SENDMSGS = &H2000000
Const MF_POSTMSGS = &H4000000
Const MF_CALLBACKS = &H8000000
Const MF_ERRORS = &H10000000
Const MF_LINKS = &H20000000
Const MF_CONV = &H40000000
Const MF_MASK = &HFF000000
' -----------------------------------------
' Win32 API error code definitions
' -----------------------------------------
' This section contains the error code definitions for the Win32 API functions.
' NO_ERROR
Const NO_ERROR = 0 ' dderror
' The configuration registry database operation completed successfully.
Const ERROR_SUCCESS = 0&
' Incorrect function.
Const ERROR_INVALID_FUNCTION = 1 ' dderror
' The system cannot find the file specified.
Const ERROR_FILE_NOT_FOUND = 2&
' The system cannot find the path specified.
Const ERROR_PATH_NOT_FOUND = 3&
' The system cannot open the file.
Const ERROR_TOO_MANY_OPEN_FILES = 4&
' Access is denied.
Const ERROR_ACCESS_DENIED = 5&
' The handle is invalid.
Const ERROR_INVALID_HANDLE = 6&
' The storage control blocks were destroyed.
Const ERROR_ARENA_TRASHED = 7&
' Not enough storage is available to process this command.
Const ERROR_NOT_ENOUGH_MEMORY = 8 ' dderror
' The storage control block address is invalid.
Const ERROR_INVALID_BLOCK = 9&
' The environment is incorrect.
Const ERROR_BAD_ENVIRONMENT = 10&
' An attempt was made to load a program with an
' incorrect format.
Const ERROR_BAD_FORMAT = 11&
' The access code is invalid.
Const ERROR_INVALID_ACCESS = 12&
' The data is invalid.
Const ERROR_INVALID_DATA = 13&
' Not enough storage is available to complete this operation.
Const ERROR_OUTOFMEMORY = 14&
' The system cannot find the drive specified.
Const ERROR_INVALID_DRIVE = 15&
' The directory cannot be removed.
Const ERROR_CURRENT_DIRECTORY = 16&
' The system cannot move the file
' to a different disk drive.
Const ERROR_NOT_SAME_DEVICE = 17&
' There are no more files.
Const ERROR_NO_MORE_FILES = 18&
' The media is write protected.
Const ERROR_WRITE_PROTECT = 19&
' The system cannot find the device specified.
Const ERROR_BAD_UNIT = 20&
' The device is not ready.
Const ERROR_NOT_READY = 21&
' The device does not recognize the command.
Const ERROR_BAD_COMMAND = 22&
' Data error (cyclic redundancy check)
Const ERROR_CRC = 23&
' The program issued a command but the
' command length is incorrect.
Const ERROR_BAD_LENGTH = 24&
' The drive cannot locate a specific
' area or track on the disk.
Const ERROR_SEEK = 25&
' The specified disk or diskette cannot be accessed.
Const ERROR_NOT_DOS_DISK = 26&
' The drive cannot find the sector requested.
Const ERROR_SECTOR_NOT_FOUND = 27&
' The printer is out of paper.
Const ERROR_OUT_OF_PAPER = 28&
' The system cannot write to the specified device.
Const ERROR_WRITE_FAULT = 29&
' The system cannot read from the specified device.
Const ERROR_READ_FAULT = 30&
' A device attached to the system is not functioning.
Const ERROR_GEN_FAILURE = 31&
' The process cannot access the file because
' it is being used by another process.
Const ERROR_SHARING_VIOLATION = 32&
' The process cannot access the file because
' another process has locked a portion of the file.
Const ERROR_LOCK_VIOLATION = 33&
' The wrong diskette is in the drive.
' Insert %2 (Volume Serial Number: %3)
' into drive %1.
Const ERROR_WRONG_DISK = 34&
' Too many files opened for sharing.
Const ERROR_SHARING_BUFFER_EXCEEDED = 36&
' Reached end of file.
Const ERROR_HANDLE_EOF = 38&
' The disk is full.
Const ERROR_HANDLE_DISK_FULL = 39&
' The network request is not supported.
Const ERROR_NOT_SUPPORTED = 50&
' The remote computer is not available.
Const ERROR_REM_NOT_LIST = 51&
' A duplicate name exists on the network.
Const ERROR_DUP_NAME = 52&
' The network path was not found.
Const ERROR_BAD_NETPATH = 53&
' The network is busy.
Const ERROR_NETWORK_BUSY = 54&
' The specified network resource or device is no longer
' available.
Const ERROR_DEV_NOT_EXIST = 55 ' dderror
' The network BIOS command limit has been reached.
Const ERROR_TOO_MANY_CMDS = 56&
' A network adapter hardware error occurred.
Const ERROR_ADAP_HDW_ERR = 57&
' The specified server cannot perform the requested
' operation.
Const ERROR_BAD_NET_RESP = 58&
' An unexpected network error occurred.
Const ERROR_UNEXP_NET_ERR = 59&
' The remote adapter is not compatible.
Const ERROR_BAD_REM_ADAP = 60&
' The printer queue is full.
Const ERROR_PRINTQ_FULL = 61&
' Space to store the file waiting to be printed is
' not available on the server.
Const ERROR_NO_SPOOL_SPACE = 62&
' Your file waiting to be printed was deleted.
Const ERROR_PRINT_CANCELLED = 63&
' The specified network name is no longer available.
Const ERROR_NETNAME_DELETED = 64&
' Network access is denied.
Const ERROR_NETWORK_ACCESS_DENIED = 65&
' The network resource type is not correct.
Const ERROR_BAD_DEV_TYPE = 66&
' The network name cannot be found.
Const ERROR_BAD_NET_NAME = 67&
' The name limit for the local computer network
' adapter card was exceeded.
Const ERROR_TOO_MANY_NAMES = 68&
' The network BIOS session limit was exceeded.
Const ERROR_TOO_MANY_SESS = 69&
' The remote server has been paused or is in the
' process of being started.
Const ERROR_SHARING_PAUSED = 70&
' The network request was not accepted.
Const ERROR_REQ_NOT_ACCEP = 71&
' The specified printer or disk device has been paused.
Const ERROR_REDIR_PAUSED = 72&
' The file exists.
Const ERROR_FILE_EXISTS = 80&
' The directory or file cannot be created.
Const ERROR_CANNOT_MAKE = 82&
' Fail on INT 24
Const ERROR_FAIL_I24 = 83&
' Storage to process this request is not available.
Const ERROR_OUT_OF_STRUCTURES = 84&
' The local device name is already in use.
Const ERROR_ALREADY_ASSIGNED = 85&
' The specified network password is not correct.
Const ERROR_INVALID_PASSWORD = 86&
' The parameter is incorrect.
Const ERROR_INVALID_PARAMETER = 87 ' dderror
' A write fault occurred on the network.
Const ERROR_NET_WRITE_FAULT = 88&
' The system cannot start another process at
' this time.
Const ERROR_NO_PROC_SLOTS = 89&
' Cannot create another system semaphore.
Const ERROR_TOO_MANY_SEMAPHORES = 100&
' The exclusive semaphore is owned by another process.
Const ERROR_EXCL_SEM_ALREADY_OWNED = 101&
' The semaphore is set and cannot be closed.
Const ERROR_SEM_IS_SET = 102&
' The semaphore cannot be set again.
Const ERROR_TOO_MANY_SEM_REQUESTS = 103&
' Cannot request exclusive semaphores at interrupt time.
Const ERROR_INVALID_AT_INTERRUPT_TIME = 104&
' The previous ownership of this semaphore has ended.
Const ERROR_SEM_OWNER_DIED = 105&
' Insert the diskette for drive %1.
Const ERROR_SEM_USER_LIMIT = 106&
' Program stopped because alternate diskette was not inserted.
Const ERROR_DISK_CHANGE = 107&
' The disk is in use or locked by
' another process.
Const ERROR_DRIVE_LOCKED = 108&
' The pipe has been ended.
Const ERROR_BROKEN_PIPE = 109&
' The system cannot open the
' device or file specified.
Const ERROR_OPEN_FAILED = 110&
' The file name is too long.
Const ERROR_BUFFER_OVERFLOW = 111&
' There is not enough space on the disk.
Const ERROR_DISK_FULL = 112&
' No more internal file identifiers available.
Const ERROR_NO_MORE_SEARCH_HANDLES = 113&
' The target internal file identifier is incorrect.
Const ERROR_INVALID_TARGET_HANDLE = 114&
' The IOCTL call made by the application program is
' not correct.
Const ERROR_INVALID_CATEGORY = 117&
' The verify-on-write switch parameter value is not
' correct.
Const ERROR_INVALID_VERIFY_SWITCH = 118&
' The system does not support the command requested.
Const ERROR_BAD_DRIVER_LEVEL = 119&
' This function is only valid in Windows NT mode.
Const ERROR_CALL_NOT_IMPLEMENTED = 120&
' The semaphore timeout period has expired.
Const ERROR_SEM_TIMEOUT = 121&
' The data area passed to a system call is too
' small.
Const ERROR_INSUFFICIENT_BUFFER = 122 ' dderror
' The filename, directory name, or volume label syntax is incorrect.
Const ERROR_INVALID_NAME = 123&
' The system call level is not correct.
Const ERROR_INVALID_LEVEL = 124&
' The disk has no volume label.
Const ERROR_NO_VOLUME_LABEL = 125&
' The specified module could not be found.
Const ERROR_MOD_NOT_FOUND = 126&
' The specified procedure could not be found.
Const ERROR_PROC_NOT_FOUND = 127&
' There are no child processes to wait for.
Const ERROR_WAIT_NO_CHILDREN = 128&
' The %1 application cannot be run in Windows NT mode.
Const ERROR_CHILD_NOT_COMPLETE = 129&
' Attempt to use a file handle to an open disk partition for an
' operation other than raw disk I/O.
Const ERROR_DIRECT_ACCESS_HANDLE = 130&
' An attempt was made to move the file pointer before the beginning of the file.
Const ERROR_NEGATIVE_SEEK = 131&
' The file pointer cannot be set on the specified device or file.
Const ERROR_SEEK_ON_DEVICE = 132&
' A JOIN or SUBST command
' cannot be used for a drive that
' contains previously joined drives.
Const ERROR_IS_JOIN_TARGET = 133&
' An attempt was made to use a
' JOIN or SUBST command on a drive that has
' already been joined.
Const ERROR_IS_JOINED = 134&
' An attempt was made to use a
' JOIN or SUBST command on a drive that has
' already been substituted.
Const ERROR_IS_SUBSTED = 135&
' The system tried to delete
' the JOIN of a drive that is not joined.
Const ERROR_NOT_JOINED = 136&
' The system tried to delete the
' substitution of a drive that is not substituted.
Const ERROR_NOT_SUBSTED = 137&
' The system tried to join a drive
' to a directory on a joined drive.
Const ERROR_JOIN_TO_JOIN = 138&
' The system tried to substitute a
' drive to a directory on a substituted drive.
Const ERROR_SUBST_TO_SUBST = 139&
' The system tried to join a drive to
' a directory on a substituted drive.
Const ERROR_JOIN_TO_SUBST = 140&
' The system tried to SUBST a drive
' to a directory on a joined drive.
Const ERROR_SUBST_TO_JOIN = 141&
' The system cannot perform a JOIN or SUBST at this time.
Const ERROR_BUSY_DRIVE = 142&
' The system cannot join or substitute a
' drive to or for a directory on the same drive.
Const ERROR_SAME_DRIVE = 143&
' The directory is not a subdirectory of the root directory.
Const ERROR_DIR_NOT_ROOT = 144&
' The directory is not empty.
Const ERROR_DIR_NOT_EMPTY = 145&
' The path specified is being used in
' a substitute.
Const ERROR_IS_SUBST_PATH = 146&
' Not enough resources are available to
' process this command.
Const ERROR_IS_JOIN_PATH = 147&
' The path specified cannot be used at this time.
Const ERROR_PATH_BUSY = 148&
' An attempt was made to join
' or substitute a drive for which a directory
' on the drive is the target of a previous
' substitute.
Const ERROR_IS_SUBST_TARGET = 149&
' System trace information was not specified in your
' CONFIG.SYS file, or tracing is disallowed.
Const ERROR_SYSTEM_TRACE = 150&
' The number of specified semaphore events for
' DosMuxSemWait is not correct.
Const ERROR_INVALID_EVENT_COUNT = 151&
' DosMuxSemWait did not execute; too many semaphores
' are already set.
Const ERROR_TOO_MANY_MUXWAITERS = 152&
' The DosMuxSemWait list is not correct.
Const ERROR_INVALID_LIST_FORMAT = 153&
' The volume label you entered exceeds the
' 11 character limit. The first 11 characters were written
' to disk. Any characters that exceeded the 11 character limit
' were automatically deleted.
Const ERROR_LABEL_TOO_LONG = 154&
' Cannot create another thread.
Const ERROR_TOO_MANY_TCBS = 155&
' The recipient process has refused the signal.
Const ERROR_SIGNAL_REFUSED = 156&
' The segment is already discarded and cannot be locked.
Const ERROR_DISCARDED = 157&
' The segment is already unlocked.
Const ERROR_NOT_LOCKED = 158&
' The address for the thread ID is not correct.
Const ERROR_BAD_THREADID_ADDR = 159&
' The argument string passed to DosExecPgm is not correct.
Const ERROR_BAD_ARGUMENTS = 160&
' The specified path is invalid.
Const ERROR_BAD_PATHNAME = 161&
' A signal is already pending.
Const ERROR_SIGNAL_PENDING = 162&
' No more threads can be created in the system.
Const ERROR_MAX_THRDS_REACHED = 164&
' Unable to lock a region of a file.
Const ERROR_LOCK_FAILED = 167&
' The requested resource is in use.
Const ERROR_BUSY = 170&
' A lock request was not outstanding for the supplied cancel region.
Const ERROR_CANCEL_VIOLATION = 173&
' The file system does not support atomic changes to the lock type.
Const ERROR_ATOMIC_LOCKS_NOT_SUPPORTED = 174&
' The system detected a segment number that was not correct.
Const ERROR_INVALID_SEGMENT_NUMBER = 180&
' The operating system cannot run %1.
Const ERROR_INVALID_ORDINAL = 182&
' Cannot create a file when that file already exists.
Const ERROR_ALREADY_EXISTS = 183&
' The flag passed is not correct.
Const ERROR_INVALID_FLAG_NUMBER = 186&
' The specified system semaphore name was not found.
Const ERROR_SEM_NOT_FOUND = 187&
' The operating system cannot run %1.
Const ERROR_INVALID_STARTING_CODESEG = 188&
' The operating system cannot run %1.
Const ERROR_INVALID_STACKSEG = 189&
' The operating system cannot run %1.
Const ERROR_INVALID_MODULETYPE = 190&
' Cannot run %1 in Windows NT mode.
Const ERROR_INVALID_EXE_SIGNATURE = 191&
' The operating system cannot run %1.
Const ERROR_EXE_MARKED_INVALID = 192&
' %1 is not a valid Windows NT application.
Const ERROR_BAD_EXE_FORMAT = 193&
' The operating system cannot run %1.
Const ERROR_ITERATED_DATA_EXCEEDS_64k = 194&
' The operating system cannot run %1.
Const ERROR_INVALID_MINALLOCSIZE = 195&
' The operating system cannot run this
' application program.
Const ERROR_DYNLINK_FROM_INVALID_RING = 196&
' The operating system is not presently
' configured to run this application.
Const ERROR_IOPL_NOT_ENABLED = 197&
' The operating system cannot run %1.
Const ERROR_INVALID_SEGDPL = 198&
' The operating system cannot run this
' application program.
Const ERROR_AUTODATASEG_EXCEEDS_64k = 199&
' The code segment cannot be greater than or equal to 64KB.
Const ERROR_RING2SEG_MUST_BE_MOVABLE = 200&
' The operating system cannot run %1.
Const ERROR_RELOC_CHAIN_XEEDS_SEGLIM = 201&
' The operating system cannot run %1.
Const ERROR_INFLOOP_IN_RELOC_CHAIN = 202&
' The system could not find the environment
' option that was entered.
Const ERROR_ENVVAR_NOT_FOUND = 203&
' No process in the command subtree has a
' signal handler.
Const ERROR_NO_SIGNAL_SENT = 205&
' The filename or extension is too long.
Const ERROR_FILENAME_EXCED_RANGE = 206&
' The ring 2 stack is in use.
Const ERROR_RING2_STACK_IN_USE = 207&
' The Global filename characters, or ?, are entered
' incorrectly or too many Global filename characters are specified.
Const ERROR_META_EXPANSION_TOO_LONG = 208&
' The signal being posted is not correct.
Const ERROR_INVALID_SIGNAL_NUMBER = 209&
' The signal handler cannot be set.
Const ERROR_THREAD_1_INACTIVE = 210&
' The segment is locked and cannot be reallocated.
Const ERROR_LOCKED = 212&
' Too many dynamic link modules are attached to this
' program or dynamic link module.
Const ERROR_TOO_MANY_MODULES = 214&
' Can't nest calls to LoadModule.
Const ERROR_NESTING_NOT_ALLOWED = 215&
' The pipe state is invalid.
Const ERROR_BAD_PIPE = 230&
' All pipe instances are busy.
Const ERROR_PIPE_BUSY = 231&
' The pipe is being closed.
Const ERROR_NO_DATA = 232&
' No process is on the other end of the pipe.
Const ERROR_PIPE_NOT_CONNECTED = 233&
' More data is available.
Const ERROR_MORE_DATA = 234 ' dderror
' The session was cancelled.
Const ERROR_VC_DISCONNECTED = 240&
' The specified extended attribute name was invalid.
Const ERROR_INVALID_EA_NAME = 254&
' The extended attributes are inconsistent.
Const ERROR_EA_LIST_INCONSISTENT = 255&
' No more data is available.
Const ERROR_NO_MORE_ITEMS = 259&
' The Copy API cannot be used.
Const ERROR_CANNOT_COPY = 266&
' The directory name is invalid.
Const ERROR_DIRECTORY = 267&
' The extended attributes did not fit in the buffer.
Const ERROR_EAS_DIDNT_FIT = 275&
' The extended attribute file on the mounted file system is corrupt.
Const ERROR_EA_FILE_CORRUPT = 276&
' The extended attribute table file is full.
Const ERROR_EA_TABLE_FULL = 277&
' The specified extended attribute handle is invalid.
Const ERROR_INVALID_EA_HANDLE = 278&
' The mounted file system does not support extended attributes.
Const ERROR_EAS_NOT_SUPPORTED = 282&
' Attempt to release mutex not owned by caller.
Const ERROR_NOT_OWNER = 288&
' Too many posts were made to a semaphore.
Const ERROR_TOO_MANY_POSTS = 298&
' The system cannot find message for message number 0x%1
' in message file for %2.
Const ERROR_MR_MID_NOT_FOUND = 317&
' Attempt to access invalid address.
Const ERROR_INVALID_ADDRESS = 487&
' Arithmetic result exceeded 32 bits.
Const ERROR_ARITHMETIC_OVERFLOW = 534&
' There is a process on other end of the pipe.
Const ERROR_PIPE_CONNECTED = 535&
' Waiting for a process to open the other end of the pipe.
Const ERROR_PIPE_LISTENING = 536&
' Access to the extended attribute was denied.
Const ERROR_EA_ACCESS_DENIED = 994&
' The I/O operation has been aborted because of either a thread exit
' or an application request.
Const ERROR_OPERATION_ABORTED = 995&
' Overlapped I/O event is not in a signalled state.
Const ERROR_IO_INCOMPLETE = 996&
' Overlapped I/O operation is in progress.
Const ERROR_IO_PENDING = 997 ' dderror
' Invalid access to memory location.
Const ERROR_NOACCESS = 998&
' Error performing inpage operation.
Const ERROR_SWAPERROR = 999&
' Recursion too deep, stack overflowed.
Const ERROR_STACK_OVERFLOW = 1001&
' The window cannot act on the sent message.
Const ERROR_INVALID_MESSAGE = 1002&
' Cannot complete this function.
Const ERROR_CAN_NOT_COMPLETE = 1003&
' Invalid flags.
Const ERROR_INVALID_FLAGS = 1004&
' The volume does not contain a recognized file system.
' Please make sure that all required file system drivers are loaded and that the
' volume is not corrupt.
Const ERROR_UNRECOGNIZED_VOLUME = 1005&
' The volume for a file has been externally altered such that the
' opened file is no longer valid.
Const ERROR_FILE_INVALID = 1006&
' The requested operation cannot be performed in full-screen mode.
Const ERROR_FULLSCREEN_MODE = 1007&
' An attempt was made to reference a token that does not exist.
Const ERROR_NO_TOKEN = 1008&
' The configuration registry database is corrupt.
Const ERROR_BADDB = 1009&
' The configuration registry key is invalid.
Const ERROR_BADKEY = 1010&
' The configuration registry key could not be opened.
Const ERROR_CANTOPEN = 1011&
' The configuration registry key could not be read.
Const ERROR_CANTREAD = 1012&
' The configuration registry key could not be written.
Const ERROR_CANTWRITE = 1013&
' One of the files in the Registry database had to be recovered
' by use of a log or alternate copy. The recovery was successful.
Const ERROR_REGISTRY_RECOVERED = 1014&
' The Registry is corrupt. The structure of one of the files that contains
' Registry data is corrupt, or the system's image of the file in memory
' is corrupt, or the file could not be recovered because the alternate
' copy or log was absent or corrupt.
Const ERROR_REGISTRY_CORRUPT = 1015&
' An I/O operation initiated by the Registry failed unrecoverably.
' The Registry could not read in, or write out, or flush, one of the files
' that contain the system's image of the Registry.
Const ERROR_REGISTRY_IO_FAILED = 1016&
' The system has attempted to load or restore a file into the Registry, but the
' specified file is not in a Registry file format.
Const ERROR_NOT_REGISTRY_FILE = 1017&
' Illegal operation attempted on a Registry key which has been marked for deletion.
Const ERROR_KEY_DELETED = 1018&
' System could not allocate the required space in a Registry log.
Const ERROR_NO_LOG_SPACE = 1019&
' Cannot create a symbolic link in a Registry key that already
' has subkeys or values.
Const ERROR_KEY_HAS_CHILDREN = 1020&
' Cannot create a stable subkey under a volatile parent key.
Const ERROR_CHILD_MUST_BE_VOLATILE = 1021&
' A notify change request is being completed and the information
' is not being returned in the caller's buffer. The caller now
' needs to enumerate the files to find the changes.
Const ERROR_NOTIFY_ENUM_DIR = 1022&
' A stop control has been sent to a service which other running services
' are dependent on.
Const ERROR_DEPENDENT_SERVICES_RUNNING = 1051&
' The requested control is not valid for this service
Const ERROR_INVALID_SERVICE_CONTROL = 1052&
' The service did not respond to the start or control request in a timely
' fashion.
Const ERROR_SERVICE_REQUEST_TIMEOUT = 1053&
' A thread could not be created for the service.
Const ERROR_SERVICE_NO_THREAD = 1054&
' The service database is locked.
Const ERROR_SERVICE_DATABASE_LOCKED = 1055&
' An instance of the service is already running.
Const ERROR_SERVICE_ALREADY_RUNNING = 1056&
' The account name is invalid or does not exist.
Const ERROR_INVALID_SERVICE_ACCOUNT = 1057&
' The specified service is disabled and cannot be started.
Const ERROR_SERVICE_DISABLED = 1058&
' Circular service dependency was specified.
Const ERROR_CIRCULAR_DEPENDENCY = 1059&
' The specified service does not exist as an installed service.
Const ERROR_SERVICE_DOES_NOT_EXIST = 1060&
' The service cannot accept control messages at this time.
Const ERROR_SERVICE_CANNOT_ACCEPT_CTRL = 1061&
' The service has not been started.
Const ERROR_SERVICE_NOT_ACTIVE = 1062&
' The service process could not connect to the service controller.
' MMRESULT error return values specific to the mixer API
'
'
Const MIXERR_BASE = 1024
Const MIXERR_INVALLINE = (MIXERR_BASE + 0)
Const MIXERR_INVALCONTROL = (MIXERR_BASE + 1)
Const MIXERR_INVALVALUE = (MIXERR_BASE + 2)
Const MIXERR_LASTERROR = (MIXERR_BASE + 2)
Const MIXER_OBJECTF_HANDLE = &H80000000
Const MIXER_OBJECTF_MIXER = &H0&
Const MIXER_OBJECTF_HMIXER = (MIXER_OBJECTF_HANDLE Or MIXER_OBJECTF_MIXER)
Const MIXER_OBJECTF_WAVEOUT = &H10000000
Const MIXER_OBJECTF_HWAVEOUT = (MIXER_OBJECTF_HANDLE Or MIXER_OBJECTF_WAVEOUT)
Const MIXER_OBJECTF_WAVEIN = &H20000000
Const MIXER_OBJECTF_HWAVEIN = (MIXER_OBJECTF_HANDLE Or MIXER_OBJECTF_WAVEIN)
Const MIXER_OBJECTF_MIDIOUT = &H30000000
Const MIXER_OBJECTF_HMIDIOUT = (MIXER_OBJECTF_HANDLE Or MIXER_OBJECTF_MIDIOUT)
Const MIXER_OBJECTF_MIDIIN = &H40000000
Const MIXER_OBJECTF_HMIDIIN = (MIXER_OBJECTF_HANDLE Or MIXER_OBJECTF_MIDIIN)
Const MIXER_OBJECTF_AUX = &H50000000
Declare Function mixerGetNumDevs Lib "winmm.dll" Alias "mixerGetNumDevs" () As Long
Type MIXERCAPS
wMid As Integer ' manufacturer id
wPid As Integer ' product id
vDriverVersion As Long ' version of the driver
szPname As String * MAXPNAMELEN ' product name
fdwSupport As Long ' misc. support bits
cDestinations As Long ' count of destinations
End Type
Declare Function mixerGetDevCaps Lib "winmm.dll" Alias "mixerGetDevCapsA" (ByVal uMxId As Long, ByVal pmxcaps As MIXERCAPS, ByVal cbmxcaps As Long) As Long
Declare Function mixerOpen Lib "winmm.dll" Alias "mixerOpen" (phmx As Long, ByVal uMxId As Long, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal fdwOpen As Long) As Long
Declare Function mixerClose Lib "winmm.dll" Alias "mixerClose" (ByVal hmx As Long) As Long
Declare Function mixerMessage Lib "winmm.dll" Alias "mixerMessage" (ByVal hmx As Long, ByVal uMsg As Long, ByVal dwParam1 As Long, ByVal dwParam2 As Long) As Long
Type Target ' for use in MIXERLINE and others (embedded structure)
dwType As Long ' MIXERLINE_TARGETTYPE_xxxx
dwDeviceID As Long ' target device ID of device type
wMid As Integer ' of target device
wPid As Integer ' "
vDriverVersion As Long ' "
szPname As String * MAXPNAMELEN
End Type
Type MIXERLINE
cbStruct As Long ' size of MIXERLINE structure
dwDestination As Long ' zero based destination index
dwSource As Long ' zero based source index (if source)
dwLineID As Long ' unique line id for mixer device
fdwLine As Long ' state/information about line
dwUser As Long ' driver specific information
dwComponentType As Long ' component type line connects to
cChannels As Long ' number of channels line supports
cConnections As Long ' number of connections (possible)
cControls As Long ' number of controls at this line
Const MIXERCONTROL_CONTROLTYPE_MICROTIME = (MIXERCONTROL_CT_CLASS_TIME Or MIXERCONTROL_CT_SC_TIME_MICROSECS Or MIXERCONTROL_CT_UNITS_UNSIGNED)
Const MIXERCONTROL_CONTROLTYPE_MILLITIME = (MIXERCONTROL_CT_CLASS_TIME Or MIXERCONTROL_CT_SC_TIME_MILLISECS Or MIXERCONTROL_CT_UNITS_UNSIGNED)
'
' MIXERLINECONTROLS
'
Type MIXERLINECONTROLS
cbStruct As Long ' size in Byte of MIXERLINECONTROLS
dwLineID As Long ' line id (from MIXERLINE.dwLineID)
' MIXER_GETLINECONTROLSF_ONEBYID or
dwControl As Long ' MIXER_GETLINECONTROLSF_ONEBYTYPE
cControls As Long ' count of controls pmxctrl points to
cbmxctrl As Long ' size in Byte of _one_ MIXERCONTROL
pamxctrl As MIXERCONTROL ' pointer to first MIXERCONTROL array
End Type
Declare Function mixerGetLineControls Lib "winmm.dll" Alias "mixerGetLineControlsA" (ByVal hmxobj As Long, pmxlc As MIXERLINECONTROLS, ByVal fdwControls As Long) As Long
Const MIXER_GETLINECONTROLSF_ALL = &H0&
Const MIXER_GETLINECONTROLSF_ONEBYID = &H1&
Const MIXER_GETLINECONTROLSF_ONEBYTYPE = &H2&
Const MIXER_GETLINECONTROLSF_QUERYMASK = &HF&
Type MIXERCONTROLDETAILS
cbStruct As Long ' size in Byte of MIXERCONTROLDETAILS
dwControlID As Long ' control id to get/set details on
cChannels As Long ' number of channels in paDetails array
item As Long ' hwndOwner or cMultipleItems
cbDetails As Long ' size of _one_ details_XX struct
paDetails As Long ' pointer to array of details_XX structs
End Type
' MIXER_GETCONTROLDETAILSF_LISTTEXT
Type MIXERCONTROLDETAILS_LISTTEXT
dwParam1 As Long
dwParam2 As Long
szName As String * MIXER_LONG_NAME_CHARS
End Type
' MIXER_GETCONTROLDETAILSF_VALUE
Type MIXERCONTROLDETAILS_BOOLEAN
fValue As Long
End Type
Type MIXERCONTROLDETAILS_SIGNED
lValue As Long
End Type
Type MIXERCONTROLDETAILS_UNSIGNED
dwValue As Long
End Type
Declare Function mixerGetControlDetails Lib "winmm.dll" Alias "mixerGetControlDetailsA" (ByVal hmxobj As Long, pmxcd As MIXERCONTROLDETAILS, ByVal fdwDetails As Long) As Long
Const MIXER_GETCONTROLDETAILSF_VALUE = &H0&
Const MIXER_GETCONTROLDETAILSF_LISTTEXT = &H1&
Const MIXER_GETCONTROLDETAILSF_QUERYMASK = &HF&
Declare Function mixerSetControlDetails Lib "winmm.dll" Alias "mixerSetControlDetails" (ByVal hmxobj As Long, pmxcd As MIXERCONTROLDETAILS, ByVal fdwDetails As Long) As Long
Const MIXER_SETCONTROLDETAILSF_VALUE = &H0&
Const MIXER_SETCONTROLDETAILSF_CUSTOM = &H1&
Const MIXER_SETCONTROLDETAILSF_QUERYMASK = &HF&
' constants used with JOYINFOEX
Const JOY_BUTTON5 = &H10&
Const JOY_BUTTON6 = &H20&
Const JOY_BUTTON7 = &H40&
Const JOY_BUTTON8 = &H80&
Const JOY_BUTTON9 = &H100&
Const JOY_BUTTON10 = &H200&
Const JOY_BUTTON11 = &H400&
Const JOY_BUTTON12 = &H800&
Const JOY_BUTTON13 = &H1000&
Const JOY_BUTTON14 = &H2000&
Const JOY_BUTTON15 = &H4000&
Const JOY_BUTTON16 = &H8000&
Const JOY_BUTTON17 = &H10000
Const JOY_BUTTON18 = &H20000
Const JOY_BUTTON19 = &H40000
Const JOY_BUTTON20 = &H80000
Const JOY_BUTTON21 = &H100000
Const JOY_BUTTON22 = &H200000
Const JOY_BUTTON23 = &H400000
Const JOY_BUTTON24 = &H800000
Const JOY_BUTTON25 = &H1000000
Const JOY_BUTTON26 = &H2000000
Const JOY_BUTTON27 = &H4000000
Const JOY_BUTTON28 = &H8000000
Const JOY_BUTTON29 = &H10000000
Const JOY_BUTTON30 = &H20000000
Const JOY_BUTTON31 = &H40000000
Const JOY_BUTTON32 = &H80000000
' constants used with JOYINFOEX structure
Const JOY_POVCENTERED = -1
Const JOY_POVFORWARD = 0
Const JOY_POVRIGHT = 9000
Const JOY_POVBACKWARD = 18000
Const JOY_POVLEFT = 27000
Const JOY_RETURNX = &H1&
Const JOY_RETURNY = &H2&
Const JOY_RETURNZ = &H4&
Const JOY_RETURNR = &H8&
Const JOY_RETURNU = &H10 ' axis 5
Const JOY_RETURNV = &H20 ' axis 6
Const JOY_RETURNPOV = &H40&
Const JOY_RETURNBUTTONS = &H80&
Const JOY_RETURNRAWDATA = &H100&
Const JOY_RETURNPOVCTS = &H200&
Const JOY_RETURNCENTERED = &H400&
Const JOY_USEDEADZONE = &H800&
Const JOY_RETURNALL = (JOY_RETURNX Or JOY_RETURNY Or JOY_RETURNZ Or JOY_RETURNR Or JOY_RETURNU Or JOY_RETURNV Or JOY_RETURNPOV Or JOY_RETURNBUTTONS)
Const JOY_CAL_READALWAYS = &H10000
Const JOY_CAL_READXYONLY = &H20000
Const JOY_CAL_READ3 = &H40000
Const JOY_CAL_READ4 = &H80000
Const JOY_CAL_READXONLY = &H100000
Const JOY_CAL_READYONLY = &H200000
Const JOY_CAL_READ5 = &H400000
Const JOY_CAL_READ6 = &H800000
Const JOY_CAL_READZONLY = &H1000000
Const JOY_CAL_READRONLY = &H2000000
Const JOY_CAL_READUONLY = &H4000000
Const JOY_CAL_READVONLY = &H8000000
Declare Function joyGetPos Lib "winmm.dll" Alias "joyGetPos" (ByVal uJoyID As Long, pji As JOYINFO) As Long
Declare Function joyGetPosEx Lib "winmm.dll" Alias "joyGetPosEx" (ByVal uJoyID As Long, pji As JOYINFOEX) As Long
Const WAVE_FORMAT_QUERY = &H1
Const SND_PURGE = &H40 ' purge non-static events for task
Const SND_APPLICATION = &H80 ' look for application specific association
Const WAVE_MAPPED = &H4
Const WAVE_FORMAT_DIRECT = &H8
Const WAVE_FORMAT_DIRECT_QUERY = (WAVE_FORMAT_QUERY Or WAVE_FORMAT_DIRECT)
Const MIM_MOREDATA = MM_MIM_MOREDATA
Const MOM_POSITIONCB = MM_MOM_POSITIONCB
' flags for dwFlags parm of midiInOpen()
Const MIDI_IO_STATUS = &H20&
Declare Function midiStreamOpen Lib "winmm.dll" Alias "midiStreamOpen" (phms As Long, puDeviceID As Long, ByVal cMidi As Long, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal fdwOpen As Long) As Long
Declare Function midiStreamClose Lib "winmm.dll" Alias "midiStreamClose" (ByVal hms As Long) As Long
Declare Function midiStreamProperty Lib "winmm.dll" Alias "midiStreamProperty" (ByVal hms As Long, lppropdata As Byte, ByVal dwProperty As Long) As Long
Declare Function midiStreamPosition Lib "winmm.dll" Alias "midiStreamPosition" (ByVal hms As Long, lpmmt As MMTIME, ByVal cbmmt As Long) As Long
Declare Function midiStreamOut Lib "winmm.dll" Alias "midiStreamOut" (ByVal hms As Long, pmh As MIDIHDR, ByVal cbmh As Long) As Long
Declare Function midiStreamPause Lib "winmm.dll" Alias "midiStreamPause" (ByVal hms As Long) As Long
Declare Function midiStreamRestart Lib "winmm.dll" Alias "midiStreamRestart" (ByVal hms As Long) As Long
Declare Function midiStreamStop Lib "winmm.dll" Alias "midiStreamStop" (ByVal hms As Long) As Long
Declare Function midiConnect Lib "winmm.dll" Alias "midiConnect" (ByVal hmi As Long, ByVal hmo As Long, pReserved As Any) As Long
Declare Function midiDisconnect Lib "winmm.dll" Alias "midiDisconnect" (ByVal hmi As Long, ByVal hmo As Long, pReserved As Any) As Long
Type JOYINFOEX
dwSize As Long ' size of structure
dwFlags As Long ' flags to indicate what to return
dwXpos As Long ' x position
dwYpos As Long ' y position
dwZpos As Long ' z position
dwRpos As Long ' rudder/4th axis position
dwUpos As Long ' 5th axis position
dwVpos As Long ' 6th axis position
dwButtons As Long ' button states
dwButtonNumber As Long ' current button number pressed
dwPOV As Long ' point of view state
dwReserved1 As Long ' reserved for communication between winmm driver
dwReserved2 As Long ' reserved for future expansion
End Type
' Installable driver support
' Driver messages
Const DRV_LOAD = &H1
Const DRV_ENABLE = &H2
Const DRV_OPEN = &H3
Const DRV_CLOSE = &H4
Const DRV_DISABLE = &H5
Const DRV_FREE = &H6
Const DRV_CONFIGURE = &H7
Const DRV_QUERYCONFIGURE = &H8
Const DRV_INSTALL = &H9
Const DRV_REMOVE = &HA
Const DRV_EXITSESSION = &HB
Const DRV_POWER = &HF
Const DRV_RESERVED = &H800
Const DRV_USER = &H4000
Type DRVCONFIGINFO
dwDCISize As Long
lpszDCISectionName As String
lpszDCIAliasName As String
dnDevNode As Long
End Type
' Supported return values for DRV_CONFIGURE message
Const DRVCNF_CANCEL = &H0
Const DRVCNF_OK = &H1
Const DRVCNF_RESTART = &H2
' return values from DriverProc() function
Const DRV_CANCEL = DRVCNF_CANCEL
Const DRV_OK = DRVCNF_OK
Const DRV_RESTART = DRVCNF_RESTART
Declare Function CloseDriver Lib "winmm.dll" Alias "CloseDriver" (ByVal hDriver As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Declare Function OpenDriver Lib "winmm.dll" Alias "OpenDriver" (ByVal szDriverName As String, ByVal szSectionName As String, ByVal lParam2 As Long) As Long
Declare Function SendDriverMessage Lib "winmm.dll" Alias "SendDriverMessage" (ByVal hDriver As Long, ByVal message As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Declare Function DrvGetModuleHandle Lib "winmm.dll" Alias "DrvGetModuleHandle" (ByVal hDriver As Long) As Long
Declare Function GetDriverModuleHandle Lib "winmm.dll" Alias "GetDriverModuleHandle" (ByVal hDriver As Long) As Long
Declare Function DefDriverProc Lib "winmm.dll" Alias "DefDriverProc" (ByVal dwDriverIdentifier As Long, ByVal hdrvr As Long, ByVal uMsg As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Const DRV_MCI_FIRST = DRV_RESERVED
Const DRV_MCI_LAST = DRV_RESERVED + &HFFF
' Driver callback support
' flags used with waveOutOpen(), waveInOpen(), midiInOpen(), and
' midiOutOpen() to specify the type of the dwCallback parameter.
Const CALLBACK_TYPEMASK = &H70000 ' callback type mask
Const CALLBACK_NULL = &H0 ' no callback
Const CALLBACK_WINDOW = &H10000 ' dwCallback is a HWND
Const CALLBACK_TASK = &H20000 ' dwCallback is a HTASK
Const CALLBACK_FUNCTION = &H30000 ' dwCallback is a FARPROC
' manufacturer IDs
Const MM_MICROSOFT = 1 ' Microsoft Corp.
' product IDs
Const MM_MIDI_MAPPER = 1 ' MIDI Mapper
Const MM_WAVE_MAPPER = 2 ' Wave Mapper
Const MM_SNDBLST_MIDIOUT = 3 ' Sound Blaster MIDI output port
Const MM_SNDBLST_MIDIIN = 4 ' Sound Blaster MIDI input port
Const WAVE_FORMAT_PCM = 1 ' Needed in resource files so outside #ifndef RC_INVOKED
Type WAVEFORMAT
wFormatTag As Integer
nChannels As Integer
nSamplesPerSec As Long
nAvgBytesPerSec As Long
nBlockAlign As Integer
End Type
Type PCMWAVEFORMAT
wf As WAVEFORMAT
wBitsPerSample As Integer
End Type
Declare Function waveOutGetNumDevs Lib "winmm.dll" Alias "waveOutGetNumDevs" () As Long
Declare Function waveOutGetDevCaps Lib "winmm.dll" Alias "waveOutGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As WAVEOUTCAPS, ByVal uSize As Long) As Long
Declare Function waveOutGetVolume Lib "winmm.dll" Alias "waveOutGetVolume" (ByVal uDeviceID As Long, lpdwVolume As Long) As Long
Declare Function waveOutSetVolume Lib "winmm.dll" Alias "waveOutSetVolume" (ByVal uDeviceID As Long, ByVal dwVolume As Long) As Long
Declare Function waveOutGetErrorText Lib "winmm.dll" Alias "waveOutGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function waveOutOpen Lib "winmm.dll" Alias "waveOutOpen" (lphWaveOut As Long, ByVal uDeviceID As Long, lpFormat As WAVEFORMAT, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function waveOutClose Lib "winmm.dll" Alias "waveOutClose" (ByVal hWaveOut As Long) As Long
Declare Function waveOutPrepareHeader Lib "winmm.dll" Alias "waveOutPrepareHeader" (ByVal hWaveOut As Long, lpWaveOutHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveOutUnprepareHeader Lib "winmm.dll" Alias "waveOutUnprepareHeader" (ByVal hWaveOut As Long, lpWaveOutHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveOutWrite Lib "winmm.dll" Alias "waveOutWrite" (ByVal hWaveOut As Long, lpWaveOutHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveOutPause Lib "winmm.dll" Alias "waveOutPause" (ByVal hWaveOut As Long) As Long
Declare Function waveOutRestart Lib "winmm.dll" Alias "waveOutRestart" (ByVal hWaveOut As Long) As Long
Declare Function waveOutReset Lib "winmm.dll" Alias "waveOutReset" (ByVal hWaveOut As Long) As Long
Declare Function waveOutBreakLoop Lib "winmm.dll" Alias "waveOutBreakLoop" (ByVal hWaveOut As Long) As Long
Declare Function waveOutGetPosition Lib "winmm.dll" Alias "waveOutGetPosition" (ByVal hWaveOut As Long, lpInfo As MMTIME, ByVal uSize As Long) As Long
Declare Function waveOutGetPitch Lib "winmm.dll" Alias "waveOutGetPitch" (ByVal hWaveOut As Long, lpdwPitch As Long) As Long
Declare Function waveOutSetPitch Lib "winmm.dll" Alias "waveOutSetPitch" (ByVal hWaveOut As Long, ByVal dwPitch As Long) As Long
Declare Function waveOutGetPlaybackRate Lib "winmm.dll" Alias "waveOutGetPlaybackRate" (ByVal hWaveOut As Long, lpdwRate As Long) As Long
Declare Function waveOutSetPlaybackRate Lib "winmm.dll" Alias "waveOutSetPlaybackRate" (ByVal hWaveOut As Long, ByVal dwRate As Long) As Long
Declare Function waveOutGetID Lib "winmm.dll" Alias "waveOutGetID" (ByVal hWaveOut As Long, lpuDeviceID As Long) As Long
Declare Function waveOutMessage Lib "winmm.dll" Alias "waveOutMessage" (ByVal hWaveOut As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
Declare Function waveInGetNumDevs Lib "winmm.dll" Alias "waveInGetNumDevs" () As Long
Declare Function waveInGetDevCaps Lib "winmm.dll" Alias "waveInGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As WAVEINCAPS, ByVal uSize As Long) As Long
Declare Function waveInGetErrorText Lib "winmm.dll" Alias "waveInGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function waveInOpen Lib "winmm.dll" Alias "waveInOpen" (lphWaveIn As Long, ByVal uDeviceID As Long, lpFormat As WAVEFORMAT, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function waveInClose Lib "winmm.dll" Alias "waveInClose" (ByVal hWaveIn As Long) As Long
Declare Function waveInPrepareHeader Lib "winmm.dll" Alias "waveInPrepareHeader" (ByVal hWaveIn As Long, lpWaveInHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveInUnprepareHeader Lib "winmm.dll" Alias "waveInUnprepareHeader" (ByVal hWaveIn As Long, lpWaveInHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveInAddBuffer Lib "winmm.dll" Alias "waveInAddBuffer" (ByVal hWaveIn As Long, lpWaveInHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveInStart Lib "winmm.dll" Alias "waveInStart" (ByVal hWaveIn As Long) As Long
Declare Function waveInStop Lib "winmm.dll" Alias "waveInStop" (ByVal hWaveIn As Long) As Long
Declare Function waveInReset Lib "winmm.dll" Alias "waveInReset" (ByVal hWaveIn As Long) As Long
Declare Function waveInGetPosition Lib "winmm.dll" Alias "waveInGetPosition" (ByVal hWaveIn As Long, lpInfo As MMTIME, ByVal uSize As Long) As Long
Declare Function waveInGetID Lib "winmm.dll" Alias "waveInGetID" (ByVal hWaveIn As Long, lpuDeviceID As Long) As Long
Declare Function waveInMessage Lib "winmm.dll" Alias "waveInMessage" (ByVal hWaveIn As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
' MIDI error return values
Const MIDIERR_UNPREPARED = (MIDIERR_BASE + 0) ' header not prepared
Const MIDIERR_STILLPLAYING = (MIDIERR_BASE + 1) ' still something playing
Const MIDIERR_NOMAP = (MIDIERR_BASE + 2) ' no current map
Const MIDIERR_NOTREADY = (MIDIERR_BASE + 3) ' hardware is still busy
Const MIDIERR_NODEVICE = (MIDIERR_BASE + 4) ' port no longer connected
Declare Function midiOutGetDevCaps Lib "winmm.dll" Alias "midiOutGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As MIDIOUTCAPS, ByVal uSize As Long) As Long
Declare Function midiOutGetVolume Lib "winmm.dll" Alias "midiOutGetVolume" (ByVal uDeviceID As Long, lpdwVolume As Long) As Long
Declare Function midiOutSetVolume Lib "winmm.dll" Alias "midiOutSetVolume" (ByVal uDeviceID As Long, ByVal dwVolume As Long) As Long
Declare Function midiOutGetErrorText Lib "winmm.dll" Alias "midiOutGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function midiOutOpen Lib "winmm.dll" Alias "midiOutOpen" (lphMidiOut As Long, ByVal uDeviceID As Long, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function midiOutClose Lib "winmm.dll" Alias "midiOutClose" (ByVal hMidiOut As Long) As Long
Declare Function midiOutPrepareHeader Lib "winmm.dll" Alias "midiOutPrepareHeader" (ByVal hMidiOut As Long, lpMidiOutHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiOutUnprepareHeader Lib "winmm.dll" Alias "midiOutUnprepareHeader" (ByVal hMidiOut As Long, lpMidiOutHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiOutShortMsg Lib "winmm.dll" Alias "midiOutShortMsg" (ByVal hMidiOut As Long, ByVal dwMsg As Long) As Long
Declare Function midiOutLongMsg Lib "winmm.dll" Alias "midiOutLongMsg" (ByVal hMidiOut As Long, lpMidiOutHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiOutReset Lib "winmm.dll" Alias "midiOutReset" (ByVal hMidiOut As Long) As Long
Declare Function midiOutCachePatches Lib "winmm.dll" Alias "midiOutCachePatches" (ByVal hMidiOut As Long, ByVal uBank As Long, lpPatchArray As Long, ByVal uFlags As Long) As Long
Declare Function midiOutCacheDrumPatches Lib "winmm.dll" Alias "midiOutCacheDrumPatches" (ByVal hMidiOut As Long, ByVal uPatch As Long, lpKeyArray As Long, ByVal uFlags As Long) As Long
Declare Function midiOutGetID Lib "winmm.dll" Alias "midiOutGetID" (ByVal hMidiOut As Long, lpuDeviceID As Long) As Long
Declare Function midiOutMessage Lib "winmm.dll" Alias "midiOutMessage" (ByVal hMidiOut As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
Declare Function midiInGetNumDevs Lib "winmm.dll" Alias "midiInGetNumDevs" () As Long
Declare Function midiInGetDevCaps Lib "winmm.dll" Alias "midiInGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As MIDIINCAPS, ByVal uSize As Long) As Long
Declare Function midiInGetErrorText Lib "winmm.dll" Alias "midiInGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function midiInOpen Lib "winmm.dll" Alias "midiInOpen" (lphMidiIn As Long, ByVal uDeviceID As Long, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function midiInClose Lib "winmm.dll" Alias "midiInClose" (ByVal hMidiIn As Long) As Long
Declare Function midiInPrepareHeader Lib "winmm.dll" Alias "midiInPrepareHeader" (ByVal hMidiIn As Long, lpMidiInHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiInUnprepareHeader Lib "winmm.dll" Alias "midiInUnprepareHeader" (ByVal hMidiIn As Long, lpMidiInHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiInAddBuffer Lib "winmm.dll" Alias "midiInAddBuffer" (ByVal hMidiIn As Long, lpMidiInHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiInStart Lib "winmm.dll" Alias "midiInStart" (ByVal hMidiIn As Long) As Long
Declare Function midiInStop Lib "winmm.dll" Alias "midiInStop" (ByVal hMidiIn As Long) As Long
Declare Function midiInReset Lib "winmm.dll" Alias "midiInReset" (ByVal hMidiIn As Long) As Long
Declare Function midiInGetID Lib "winmm.dll" Alias "midiInGetID" (ByVal hMidiIn As Long, lpuDeviceID As Long) As Long
Declare Function midiInMessage Lib "winmm.dll" Alias "midiInMessage" (ByVal hMidiIn As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
' device ID for aux device mapper
Const AUX_MAPPER = -1&
Type AUXCAPS
wMid As Integer
wPid As Integer
vDriverVersion As Long
szPname As String * MAXPNAMELEN
wTechnology As Integer
dwSupport As Long
End Type
' flags for wTechnology field in AUXCAPS structure
Const AUXCAPS_CDAUDIO = 1 ' audio from internal CD-ROM drive
Const AUXCAPS_AUXIN = 2 ' audio from auxiliary input jacks
' flags for dwSupport field in AUXCAPS structure
Const AUXCAPS_VOLUME = &H1 ' supports volume control
Const AUXCAPS_LRVOLUME = &H2 ' separate left-right volume control
Declare Function auxGetNumDevs Lib "winmm.dll" Alias "auxGetNumDevs" () As Long
Declare Function auxGetDevCaps Lib "winmm.dll" Alias "auxGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As AUXCAPS, ByVal uSize As Long) As Long
Declare Function auxSetVolume Lib "winmm.dll" Alias "auxSetVolume" (ByVal uDeviceID As Long, ByVal dwVolume As Long) As Long
Declare Function auxGetVolume Lib "winmm.dll" Alias "auxGetVolume" (ByVal uDeviceID As Long, lpdwVolume As Long) As Long
Declare Function auxOutMessage Lib "winmm.dll" Alias "auxOutMessage" (ByVal uDeviceID As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
' timer error return values
Const TIMERR_NOERROR = (0) ' no error
Const TIMERR_NOCANDO = (TIMERR_BASE + 1) ' request not completed
Const TIMERR_STRUCT = (TIMERR_BASE + 33) ' time struct size
' flags for wFlags parameter of timeSetEvent() function
Const TIME_ONESHOT = 0 ' program timer for single event
Const TIME_PERIODIC = 1 ' program for continuous periodic event
Type TIMECAPS
wPeriodMin As Long
wPeriodMax As Long
End Type
Declare Function timeGetSystemTime Lib "winmm.dll" Alias "timeGetSystemTime" (lpTime As MMTIME, ByVal uSize As Long) As Long
Declare Function timeGetTime Lib "winmm.dll" Alias "timeGetTime" () As Long
Declare Function timeSetEvent Lib "winmm.dll" Alias "timeSetEvent" (ByVal uDelay As Long, ByVal uResolution As Long, ByVal lpFunction As Long, ByVal dwUser As Long, ByVal uFlags As Long) As Long
Declare Function timeKillEvent Lib "winmm.dll" Alias "timeKillEvent" (ByVal uID As Long) As Long
Declare Function timeGetDevCaps Lib "winmm.dll" Alias "timeGetDevCaps" (lpTimeCaps As TIMECAPS, ByVal uSize As Long) As Long
Declare Function timeBeginPeriod Lib "winmm.dll" Alias "timeBeginPeriod" (ByVal uPeriod As Long) As Long
Declare Function timeEndPeriod Lib "winmm.dll" Alias "timeEndPeriod" (ByVal uPeriod As Long) As Long
' joystick error return values
Const JOYERR_NOERROR = (0) ' no error
Const JOYERR_PARMS = (JOYERR_BASE + 5) ' bad parameters
Const JOYERR_NOCANDO = (JOYERR_BASE + 6) ' request not completed
Const JOYERR_UNPLUGGED = (JOYERR_BASE + 7) ' joystick is unplugged
' constants used with JOYINFO structure and MM_JOY messages
Const JOY_BUTTON1 = &H1
Const JOY_BUTTON2 = &H2
Const JOY_BUTTON3 = &H4
Const JOY_BUTTON4 = &H8
Const JOY_BUTTON1CHG = &H100
Const JOY_BUTTON2CHG = &H200
Const JOY_BUTTON3CHG = &H400
Const JOY_BUTTON4CHG = &H800
' joystick ID constants
Const JOYSTICKID1 = 0
Const JOYSTICKID2 = 1
Type JOYCAPS
wMid As Integer
wPid As Integer
szPname As String * MAXPNAMELEN
wXmin As Integer
wXmax As Integer
wYmin As Integer
wYmax As Integer
wZmin As Integer
wZmax As Integer
wNumButtons As Integer
wPeriodMin As Integer
wPeriodMax As Integer
End Type
Type JOYINFO
wXpos As Long
wYpos As Long
wZpos As Long
wButtons As Long
End Type
Declare Function joyGetDevCaps Lib "winmm.dll" Alias "joyGetDevCapsA" (ByVal id As Long, lpCaps As JOYCAPS, ByVal uSize As Long) As Long
Declare Function joyGetNumDevs Lib "winmm.dll" Alias "joyGetNumDev" () As Long
Declare Function joyGetThreshold Lib "winmm.dll" Alias "joyGetThreshold" (ByVal id As Long, lpuThreshold As Long) As Long
Declare Function joyReleaseCapture Lib "winmm.dll" Alias "joyReleaseCapture" (ByVal id As Long) As Long
Declare Function joySetCapture Lib "winmm.dll" Alias "joySetCapture" (ByVal hwnd As Long, ByVal uID As Long, ByVal uPeriod As Long, ByVal bChanged As Long) As Long
Declare Function joySetThreshold Lib "winmm.dll" Alias "joySetThreshold" (ByVal id As Long, ByVal uThreshold As Long) As Long
' MMIO error return values
Const MMIOERR_BASE = 256
Const MMIOERR_FILENOTFOUND = (MMIOERR_BASE + 1) ' file not found
Const MMIOERR_OUTOFMEMORY = (MMIOERR_BASE + 2) ' out of memory
Const MMIOERR_CANNOTOPEN = (MMIOERR_BASE + 3) ' cannot open
Const MMIOERR_CANNOTCLOSE = (MMIOERR_BASE + 4) ' cannot close
Declare Function mmioStringToFOURCC Lib "winmm.dll" Alias "mmioStringToFOURCCA" (ByVal sz As String, ByVal uFlags As Long) As Long
Declare Function mmioOpen Lib "winmm.dll" Alias "mmioOpenA" (ByVal szFileName As String, lpmmioinfo As MMIOINFO, ByVal dwOpenFlags As Long) As Long
Declare Function mmioRename Lib "winmm.dll" Alias "mmioRenameA" (ByVal szFileName As String, ByVal SzNewFileName As String, lpmmioinfo As MMIOINFO, ByVal dwRenameFlags As Long) As Long
Declare Function mmioClose Lib "winmm.dll" Alias "mmioClose" (ByVal hmmio As Long, ByVal uFlags As Long) As Long
Declare Function mmioRead Lib "winmm.dll" Alias "mmioRead" (ByVal hmmio As Long, ByVal pch As String, ByVal cch As Long) As Long
Declare Function mmioWrite Lib "winmm.dll" Alias "mmioWrite" (ByVal hmmio As Long, ByVal pch As String, ByVal cch As Long) As Long
Declare Function mmioSeek Lib "winmm.dll" Alias "mmioSeek" (ByVal hmmio As Long, ByVal lOffset As Long, ByVal iOrigin As Long) As Long
Declare Function mmioGetInfo Lib "winmm.dll" Alias "mmioGetInfo" (ByVal hmmio As Long, lpmmioinfo As MMIOINFO, ByVal uFlags As Long) As Long
Declare Function mmioSetInfo Lib "winmm.dll" Alias "mmioSetInfo" (ByVal hmmio As Long, lpmmioinfo As MMIOINFO, ByVal uFlags As Long) As Long
Declare Function mmioSetBuffer Lib "winmm.dll" Alias "mmioSetBuffer" (ByVal hmmio As Long, ByVal pchBuffer As String, ByVal cchBuffer As Long, ByVal uFlags As Long) As Long
Declare Function mmioFlush Lib "winmm.dll" Alias "mmioFlush" (ByVal hmmio As Long, ByVal uFlags As Long) As Long
Declare Function mmioAdvance Lib "winmm.dll" Alias "mmioAdvance" (ByVal hmmio As Long, lpmmioinfo As MMIOINFO, ByVal uFlags As Long) As Long
Declare Function mmioSendMessage Lib "winmm.dll" Alias "mmioSendMessage" (ByVal hmmio As Long, ByVal uMsg As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Declare Function mmioDescend Lib "winmm.dll" Alias "mmioDescend" (ByVal hmmio As Long, lpck As MMCKINFO, lpckParent As MMCKINFO, ByVal uFlags As Long) As Long
Declare Function mmioAscend Lib "winmm.dll" Alias "mmioAscend" (ByVal hmmio As Long, lpck As MMCKINFO, ByVal uFlags As Long) As Long
Declare Function mmioCreateChunk Lib "winmm.dll" Alias "mmioCreateChunk" (ByVal hmmio As Long, lpck As MMCKINFO, ByVal uFlags As Long) As Long
' MCI functions
Declare Function mciSendCommand Lib "winmm.dll" Alias "mciSendCommandA" (ByVal wDeviceID As Long, ByVal uMessage As Long, ByVal dwParam1 As Long, ByVal dwParam2 As Any) As Long
Declare Function mciSendString Lib "winmm.dll" Alias "mciSendStringA" (ByVal lpstrCommand As String, ByVal lpstrReturnString As String, ByVal uReturnLength As Long, ByVal hwndCallback As Long) As Long
Declare Function mciGetCreatorTask Lib "winmm.dll" Alias "mciGetCreatorTask" (ByVal wDeviceID As Long) As Long
Declare Function mciGetDeviceID Lib "winmm.dll" Alias "mciGetDeviceIDA" (ByVal lpstrName As String) As Long
Declare Function mciGetDeviceIDFromElementID Lib "winmm.dll" Alias "mciGetDeviceIDFromElementIDA" (ByVal dwElementID As Long, ByVal lpstrType As String) As Long
Declare Function mciGetErrorString Lib "winmm.dll" Alias "mciGetErrorStringA" (ByVal dwError As Long, ByVal lpstrBuffer As String, ByVal uLength As Long) As Long
Declare Function mciExecute Lib "winmm.dll" Alias "mciExecute" (ByVal lpstrCommand As String) As Long
' flags for dwFlags parameter of MCI_PUT command message
Const MCI_ANIM_RECT = &H10000
Const MCI_ANIM_PUT_SOURCE = &H20000 ' also MCI_WHERE
Const MCI_ANIM_PUT_DESTINATION = &H40000 ' also MCI_WHERE
' flags for dwFlags parameter of MCI_WHERE command message
Const MCI_ANIM_WHERE_SOURCE = &H20000
Const MCI_ANIM_WHERE_DESTINATION = &H40000
' flags for dwFlags parameter of MCI_UPDATE command message
Const MCI_ANIM_UPDATE_HDC = &H20000
Type MCI_ANIM_OPEN_PARMS
dwCallback As Long
wDeviceID As Long
lpstrDeviceType As String
lpstrElementName As String
lpstrAlias As String
dwStyle As Long
hWndParent As Long
End Type
Type MCI_ANIM_PLAY_PARMS
dwCallback As Long
dwFrom As Long
dwTo As Long
dwSpeed As Long
End Type
Type MCI_ANIM_STEP_PARMS
dwCallback As Long
dwFrames As Long
End Type
Type MCI_ANIM_WINDOW_PARMS
dwCallback As Long
hwnd As Long
nCmdShow As Long
lpstrText As String
End Type
Type MCI_ANIM_RECT_PARMS
dwCallback As Long
rc As Rect
End Type
Type MCI_ANIM_UPDATE_PARMS
dwCallback As Long
rc As Rect
hdc As Long
End Type
' flags for dwFlags parameter of MCI_OPEN command message
Const MCI_OVLY_OPEN_WS = &H10000
Const MCI_OVLY_OPEN_PARENT = &H20000
' flags for dwFlags parameter of MCI_STATUS command message
Const MCI_OVLY_STATUS_HWND = &H4001&
Const MCI_OVLY_STATUS_STRETCH = &H4002&
' flags for dwFlags parameter of MCI_INFO command message
Const MCI_OVLY_INFO_TEXT = &H10000
' flags for dwItem field of MCI_GETDEVCAPS_PARMS parameter block
Const MCI_OVLY_GETDEVCAPS_CAN_STRETCH = &H4001&
Const MCI_OVLY_GETDEVCAPS_CAN_FREEZE = &H4002&
Const MCI_OVLY_GETDEVCAPS_MAX_WINDOWS = &H4003&
' flags for dwFlags parameter of MCI_WINDOW command message
Const MCI_OVLY_WINDOW_HWND = &H10000
Const MCI_OVLY_WINDOW_STATE = &H40000
Const MCI_OVLY_WINDOW_TEXT = &H80000
Const MCI_OVLY_WINDOW_ENABLE_STRETCH = &H100000
Const MCI_OVLY_WINDOW_DISABLE_STRETCH = &H200000
' flags for hWnd parameter of MCI_OVLY_WINDOW_PARMS parameter block
Const MCI_OVLY_WINDOW_DEFAULT = &H0&
' flags for dwFlags parameter of MCI_PUT command message
Const MCI_OVLY_RECT = &H10000
Const MCI_OVLY_PUT_SOURCE = &H20000
Const MCI_OVLY_PUT_DESTINATION = &H40000
Const MCI_OVLY_PUT_FRAME = &H80000
Const MCI_OVLY_PUT_VIDEO = &H100000
' flags for dwFlags parameter of MCI_WHERE command message
Const MCI_OVLY_WHERE_SOURCE = &H20000
Const MCI_OVLY_WHERE_DESTINATION = &H40000
Const MCI_OVLY_WHERE_FRAME = &H80000
Const MCI_OVLY_WHERE_VIDEO = &H100000
Type MCI_OVLY_OPEN_PARMS
dwCallback As Long
wDeviceID As Long
lpstrDeviceType As String
lpstrElementName As String
lpstrAlias As String
dwStyle As Long
hWndParent As Long
End Type
Type MCI_OVLY_WINDOW_PARMS
dwCallback As Long
hwnd As Long
nCmdShow As Long
lpstrText As String
End Type
Type MCI_OVLY_RECT_PARMS
dwCallback As Long
rc As Rect
End Type
Type MCI_OVLY_SAVE_PARMS
dwCallback As Long
lpFileName As String
rc As Rect
End Type
Type MCI_OVLY_LOAD_PARMS
dwCallback As Long
lpFileName As String
rc As Rect
End Type
Const CAPS1 = 94 ' other caps
Const C1_TRANSPARENT = &H1 ' new raster cap
Const NEWTRANSPARENT = 3 ' use with SetBkMode()
Const QUERYROPSUPPORT = 40 ' use to determine ROP support
Const SELECTDIB = 41 ' DIB.DRV select dib escape
' ----------------
' shell association database management functions
' -----------------
' error values for ShellExecute() beyond the regular WinExec() codes
Const SE_ERR_SHARE = 26
Const SE_ERR_ASSOCINCOMPLETE = 27
Const SE_ERR_DDETIMEOUT = 28
Const SE_ERR_DDEFAIL = 29
Const SE_ERR_DDEBUSY = 30
Const SE_ERR_NOASSOC = 31
' -------------
' Print APIs
' -------------
Type PRINTER_INFO_1
flags As Long
pDescription As String
pName As String
pComment As String
End Type
Type PRINTER_INFO_2
pServerName As String
pPrinterName As String
pShareName As String
pPortName As String
pDriverName As String
pComment As String
pLocation As String
pDevMode As DEVMODE
pSepFile As String
pPrintProcessor As String
pDatatype As String
pParameters As String
pSecurityDescriptor As SECURITY_DESCRIPTOR
Attributes As Long
Priority As Long
DefaultPriority As Long
StartTime As Long
UntilTime As Long
Status As Long
cJobs As Long
AveragePPM As Long
End Type
Type PRINTER_INFO_3
pSecurityDescriptor As SECURITY_DESCRIPTOR
End Type
Const PRINTER_CONTROL_PAUSE = 1
Const PRINTER_CONTROL_RESUME = 2
Const PRINTER_CONTROL_PURGE = 3
Const PRINTER_STATUS_PAUSED = &H1
Const PRINTER_STATUS_ERROR = &H2
Const PRINTER_STATUS_PENDING_DELETION = &H4
Const PRINTER_STATUS_PAPER_JAM = &H8
Const PRINTER_STATUS_PAPER_OUT = &H10
Const PRINTER_STATUS_MANUAL_FEED = &H20
Const PRINTER_STATUS_PAPER_PROBLEM = &H40
Const PRINTER_STATUS_OFFLINE = &H80
Const PRINTER_STATUS_IO_ACTIVE = &H100
Const PRINTER_STATUS_BUSY = &H200
Const PRINTER_STATUS_PRINTING = &H400
Const PRINTER_STATUS_OUTPUT_BIN_FULL = &H800
Const PRINTER_STATUS_NOT_AVAILABLE = &H1000
Const PRINTER_STATUS_WAITING = &H2000
Const PRINTER_STATUS_PROCESSING = &H4000
Const PRINTER_STATUS_INITIALIZING = &H8000
Const PRINTER_STATUS_WARMING_UP = &H10000
Const PRINTER_STATUS_TONER_LOW = &H20000
Const PRINTER_STATUS_NO_TONER = &H40000
Const PRINTER_STATUS_PAGE_PUNT = &H80000
Const PRINTER_STATUS_USER_INTERVENTION = &H100000
Const PRINTER_STATUS_OUT_OF_MEMORY = &H200000
Const PRINTER_STATUS_DOOR_OPEN = &H400000
Const PRINTER_ATTRIBUTE_QUEUED = &H1
Const PRINTER_ATTRIBUTE_DIRECT = &H2
Const PRINTER_ATTRIBUTE_DEFAULT = &H4
Const PRINTER_ATTRIBUTE_SHARED = &H8
Const PRINTER_ATTRIBUTE_NETWORK = &H10
Const PRINTER_ATTRIBUTE_HIDDEN = &H20
Const PRINTER_ATTRIBUTE_LOCAL = &H40
Const NO_PRIORITY = 0
Const MAX_PRIORITY = 99
Const MIN_PRIORITY = 1
Const DEF_PRIORITY = 1
Type JOB_INFO_1
JobId As Long
pPrinterName As String
pMachineName As String
pUserName As String
pDocument As String
pDatatype As String
pStatus As String
Status As Long
Priority As Long
Position As Long
TotalPages As Long
PagesPrinted As Long
Submitted As SYSTEMTIME
End Type
Type JOB_INFO_2
JobId As Long
pPrinterName As String
pMachineName As String
pUserName As String
pDocument As String
pNotifyName As String
pDatatype As String
pPrintProcessor As String
pParameters As String
pDriverName As String
pDevMode As DEVMODE
pStatus As String
pSecurityDescriptor As SECURITY_DESCRIPTOR
Status As Long
Priority As Long
Position As Long
StartTime As Long
UntilTime As Long
TotalPages As Long
Size As Long
Submitted As SYSTEMTIME
time As Long
PagesPrinted As Long
End Type
Const JOB_CONTROL_PAUSE = 1
Const JOB_CONTROL_RESUME = 2
Const JOB_CONTROL_CANCEL = 3
Const JOB_CONTROL_RESTART = 4
Const JOB_STATUS_PAUSED = &H1
Const JOB_STATUS_ERROR = &H2
Const JOB_STATUS_DELETING = &H4
Const JOB_STATUS_SPOOLING = &H8
Const JOB_STATUS_PRINTING = &H10
Const JOB_STATUS_OFFLINE = &H20
Const JOB_STATUS_PAPEROUT = &H40
Const JOB_STATUS_PRINTED = &H80
Const JOB_POSITION_UNSPECIFIED = 0
Type ADDJOB_INFO_1
Path As String
JobId As Long
End Type
Type DRIVER_INFO_1
pName As String
End Type
Type DRIVER_INFO_2
cVersion As Long
pName As String
pEnvironment As String
pDriverPath As String
pDataFile As String
pConfigFile As String
End Type
Type DOC_INFO_1
pDocName As String
pOutputFile As String
pDatatype As String
End Type
Type FORM_INFO_1
pName As String
Size As SIZEL
ImageableArea As RECTL
End Type
Const FORM_BUILTIN = &H1
Type PRINTPROCESSOR_INFO_1
pName As String
End Type
Type PORT_INFO_1
pName As String
End Type
Type MONITOR_INFO_1
pName As String
End Type
Type MONITOR_INFO_2
pName As String
pEnvironment As String
pDLLName As String
End Type
Type DATATYPES_INFO_1
pName As String
End Type
Type PRINTER_DEFAULTS
pDatatype As String
pDevMode As DEVMODE
DesiredAccess As Long
End Type
Type PRINTER_INFO_4
pPrinterName As String
pServerName As String
Attributes As Long
End Type
Type PRINTER_INFO_5
pPrinterName As String
pPortName As String
Attributes As Long
DeviceNotSelectedTimeout As Long
TransmissionRetryTimeout As Long
End Type
Const PRINTER_CONTROL_SET_STATUS = 4
Const PRINTER_ATTRIBUTE_WORK_OFFLINE = &H400
Const PRINTER_ATTRIBUTE_ENABLE_BIDI = &H800
Const JOB_CONTROL_DELETE = 5
Const JOB_STATUS_USER_INTERVENTION = &H10000
Type DRIVER_INFO_3
cVersion As Long
pName As String ' QMS 810
pEnvironment As String ' Win32 x86
pDriverPath As String ' c:\drivers\pscript.dll
pDataFile As String ' c:\drivers\QMS810.PPD
pConfigFile As String ' c:\drivers\PSCRPTUI.DLL
pHelpFile As String ' c:\drivers\PSCRPTUI.HLP
pDependentFiles As String '
pMonitorName As String ' "PJL monitor"
pDefaultDataType As String ' "EMF"
End Type
Type DOC_INFO_2
pDocName As String
pOutputFile As String
pDatatype As String
dwMode As Long
JobId As Long
End Type
Const DI_CHANNEL = 1 ' start direct read/write channel,
Const DI_READ_SPOOL_JOB = 3
Type PORT_INFO_2
pPortName As String
pMonitorName As String
pDescription As String
fPortType As Long
Reserved As Long
End Type
Const PORT_TYPE_WRITE = &H1
Const PORT_TYPE_READ = &H2
Const PORT_TYPE_REDIRECTED = &H4
Const PORT_TYPE_NET_ATTACHED = &H8
Declare Function EnumPrinters Lib "winspool.drv" Alias "EnumPrintersA" (ByVal flags As Long, ByVal name As String, ByVal Level As Long, pPrinterEnum As Byte, ByVal cdBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
Declare Function EnumPrinterPropertySheets Lib "winspool.drv" Alias "EnumPrinterPropertySheets" (hPrinter As Long, hwnd As Long, lpfnAdd As Long, ByVal lParam As Long) As Long
Const PRINTER_ENUM_DEFAULT = &H1
Const PRINTER_ENUM_LOCAL = &H2
Const PRINTER_ENUM_CONNECTIONS = &H4
Const PRINTER_ENUM_FAVORITE = &H4
Const PRINTER_ENUM_NAME = &H8
Const PRINTER_ENUM_REMOTE = &H10
Const PRINTER_ENUM_SHARED = &H20
Const PRINTER_ENUM_NETWORK = &H40
Const PRINTER_ENUM_EXPAND = &H4000
Const PRINTER_ENUM_CONTAINER = &H8000
Const PRINTER_ENUM_ICONMASK = &HFF0000
Const PRINTER_ENUM_ICON1 = &H10000
Const PRINTER_ENUM_ICON2 = &H20000
Const PRINTER_ENUM_ICON3 = &H40000
Const PRINTER_ENUM_ICON4 = &H80000
Const PRINTER_ENUM_ICON5 = &H100000
Const PRINTER_ENUM_ICON6 = &H200000
Const PRINTER_ENUM_ICON7 = &H400000
Const PRINTER_ENUM_ICON8 = &H800000
Declare Function OpenPrinter Lib "winspool.drv" Alias "OpenPrinterA" (ByVal pPrinterName As String, phPrinter As Long, pDefault As PRINTER_DEFAULTS) As Long
Declare Function ResetPrinter Lib "winspool.drv" Alias "ResetPrinterA" (ByVal hPrinter As Long, pDefault As PRINTER_DEFAULTS) As Long
Declare Function SetJob Lib "winspool.drv" Alias "SetJobA" (ByVal hPrinter As Long, ByVal JobId As Long, ByVal Level As Long, pJob As Byte, ByVal Command As Long) As Long
Declare Function GetJob Lib "winspool.drv" Alias "GetJobA" (ByVal hPrinter As Long, ByVal JobId As Long, ByVal Level As Long, pJob As Byte, ByVal cdBuf As Long, pcbNeeded As Long) As Long
Declare Function EnumJobs Lib "winspool.drv" Alias "EnumJobsA" (ByVal hPrinter As Long, ByVal FirstJob As Long, ByVal NoJobs As Long, ByVal Level As Long, pJob As Byte, ByVal cdBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
Declare Function AddPrinter Lib "winspool.drv" Alias "AddPrinterA" (ByVal pName As String, ByVal Level As Long, pPrinter As Any) As Long
Declare Function AddPrinterDriver Lib "winspool.drv" Alias "AddPrinterDriverA" (ByVal pName As String, ByVal Level As Long, pDriverInfo As Any) As Long
Declare Function EnumPrinterDrivers Lib "winspool.drv" Alias "EnumPrinterDriversA" (ByVal pName As String, ByVal pEnvironment As String, ByVal Level As Long, pDriverInfo As Byte, ByVal cdBuf As Long, pcbNeeded As Long, pcRetruned As Long) As Long
Declare Function GetPrinterDriver Lib "winspool.drv" Alias "GetPrinterDriverA" (ByVal hPrinter As Long, ByVal pEnvironment As String, ByVal Level As Long, pDriverInfo As Byte, ByVal cdBuf As Long, pcbNeeded As Long) As Long
Declare Function GetPrinterDriverDirectory Lib "winspool.drv" Alias "GetPrinterDriverDirectoryA" (ByVal pName As String, ByVal pEnvironment As String, ByVal Level As Long, pDriverDirectory As Byte, ByVal cdBuf As Long, pcbNeeded As Long) As Long
Declare Function DeletePrinterDriver Lib "winspool.drv" Alias "DeletePrinterDriverA" (ByVal pName As String, ByVal pEnvironment As String, ByVal pDriverName As String) As Long
Declare Function AddPrintProcessor Lib "winspool.drv" Alias "AddPrintProcessorA" (ByVal pName As String, ByVal pEnvironment As String, ByVal pPathName As String, ByVal pPrintProcessorName As String) As Long
Declare Function EnumPrintProcessors Lib "winspool.drv" Alias "EnumPrintProcessorsA" (ByVal pName As String, ByVal pEnvironment As String, ByVal Level As Long, pPrintProcessorInfo As Byte, ByVal cdBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
Declare Function GetPrintProcessorDirectory Lib "winspool.drv" Alias "GetPrintProcessorDirectoryA" (ByVal pName As String, ByVal pEnvironment As String, ByVal Level As Long, ByVal pPrintProcessorInfo As String, ByVal cdBuf As Long, pcbNeeded As Long) As Long
Declare Function EnumPrintProcessorDatatypes Lib "winspool.drv" Alias "EnumPrintProcessorDatatypesA" (ByVal pName As String, ByVal pPrintProcessorName As String, ByVal Level As Long, pDatatypes As Byte, ByVal cdBuf As Long, pcbNeeded As Long, pcRetruned As Long) As Long
Declare Function DeletePrintProcessor Lib "winspool.drv" Alias "DeletePrintProcessorA" (ByVal pName As String, ByVal pEnvironment As String, ByVal pPrintProcessorName As String) As Long
Declare Function StartDocPrinter Lib "winspool.drv" Alias "StartDocPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, pDocInfo As Byte) As Long
Declare Function StartPagePrinter Lib "winspool.drv" Alias "StartPagePrinter" (ByVal hPrinter As Long) As Long
Declare Function WritePrinter Lib "winspool.drv" Alias "WritePrinter" (ByVal hPrinter As Long, pBuf As Any, ByVal cdBuf As Long, pcWritten As Long) As Long
Declare Function EndPagePrinter Lib "winspool.drv" Alias "EndPagePrinter" (ByVal hPrinter As Long) As Long
Declare Function AbortPrinter Lib "winspool.drv" Alias "AbortPrinter" (ByVal hPrinter As Long) As Long
Declare Function ReadPrinter Lib "winspool.drv" Alias "ReadPrinter" (ByVal hPrinter As Long, pBuf As Any, ByVal cdBuf As Long, pNoBytesRead As Long) As Long
Declare Function EndDocPrinter Lib "winspool.drv" Alias "EndDocPrinter" (ByVal hPrinter As Long) As Long
Declare Function AddJob Lib "winspool.drv" Alias "AddJobA" (ByVal hPrinter As Long, ByVal Level As Long, pData As Byte, ByVal cdBuf As Long, pcbNeeded As Long) As Long
Declare Function ScheduleJob Lib "winspool.drv" Alias "ScheduleJob" (ByVal hPrinter As Long, ByVal JobId As Long) As Long
Declare Function PrinterProperties Lib "winspool.drv" Alias "PrinterProperties" (ByVal hwnd As Long, ByVal hPrinter As Long) As Long
Declare Function DocumentProperties Lib "winspool.drv" Alias "DocumentPropertiesA" (ByVal hwnd As Long, ByVal hPrinter As Long, ByVal pDeviceName As String, pDevModeOutput As DEVMODE, pDevModeInput As DEVMODE, ByVal fMode As Long) As Long
Declare Function AdvancedDocumentProperties Lib "winspool.drv" Alias "AdvancedDocumentPropertiesA" (ByVal hwnd As Long, ByVal hPrinter As Long, ByVal pDeviceName As String, pDevModeOutput As DEVMODE, pDevModeInput As DEVMODE) As Long
Declare Function GetPrinterData Lib "winspool.drv" Alias "GetPrinterDataA" (ByVal hPrinter As Long, ByVal pValueName As String, pType As Long, pData As Byte, ByVal nSize As Long, pcbNeeded As Long) As Long
Declare Function SetPrinterData Lib "winspool.drv" Alias "SetPrinterDataA" (ByVal hPrinter As Long, ByVal pValueName As String, ByVal dwType As Long, pData As Byte, ByVal cbData As Long) As Long
Declare Function WaitForPrinterChange Lib "winspool.drv" Alias "WaitForPrinterChange" (ByVal hPrinter As Long, ByVal flags As Long) As Long
Declare Function PrinterMessageBox Lib "winspool.drv" Alias "PrinterMessageBoxA" (ByVal hPrinter As Long, ByVal error As Long, ByVal hwnd As Long, ByVal pText As String, ByVal pCaption As String, ByVal dwType As Long) As Long
Const PRINTER_ERROR_INFORMATION = &H80000000
Const PRINTER_ERROR_WARNING = &H40000000
Const PRINTER_ERROR_SEVERE = &H20000000
Const PRINTER_ERROR_OUTOFPAPER = &H1
Const PRINTER_ERROR_JAM = &H2
Const PRINTER_ERROR_OUTOFTONER = &H4
Declare Function ClosePrinter Lib "winspool.drv" Alias "ClosePrinter" (ByVal hPrinter As Long) As Long
Declare Function AddForm Lib "winspool.drv" Alias "AddFormA" (ByVal hPrinter As Long, ByVal Level As Long, pForm As Byte) As Long
Declare Function DeleteForm Lib "winspool.drv" Alias "DeleteFormA" (ByVal hPrinter As Long, ByVal pFormName As String) As Long
Declare Function GetForm Lib "winspool.drv" Alias "GetFormA" (ByVal hPrinter As Long, ByVal pFormName As String, ByVal Level As Long, pForm As Byte, ByVal cbBuf As Long, pcbNeeded As Long) As Long
Declare Function SetForm Lib "winspool.drv" Alias "SetFormA" (ByVal hPrinter As Long, ByVal pFormName As String, ByVal Level As Long, pForm As Byte) As Long
Declare Function EnumForms Lib "winspool.drv" Alias "EnumFormsA" (ByVal hPrinter As Long, ByVal Level As Long, pForm As Byte, ByVal cbBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
Declare Function EnumMonitors Lib "winspool.drv" Alias "EnumMonitorsA" (ByVal pName As String, ByVal Level As Long, pMonitors As Byte, ByVal cbBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
Declare Function AddMonitor Lib "winspool.drv" Alias "AddMonitorA" (ByVal pName As String, ByVal Level As Long, pMonitors As Byte) As Long
Declare Function DeleteMonitor Lib "winspool.drv" Alias "DeleteMonitorA" (ByVal pName As String, ByVal pEnvironment As String, ByVal pMonitorName As String) As Long
Declare Function EnumPorts Lib "winspool.drv" Alias "EnumPortsA" (ByVal pName As String, ByVal Level As Long, ByVal lpbPorts As Long, ByVal cbBuf As Long, pcbNeeded As Long, pcReturned As Long) As Long
Declare Function AddPort Lib "winspool.drv" Alias "AddPortA" (ByVal pName As String, ByVal hwnd As Long, ByVal pMonitorName As String) As Long
Declare Function ConfigurePort Lib "winspool.drv" Alias "ConfigurePortA" (ByVal pName As String, ByVal hwnd As Long, ByVal pPortName As String) As Long
Declare Function DeletePort Lib "winspool.drv" Alias "DeletePortA" (ByVal pName As String, ByVal hwnd As Long, ByVal pPortName As String) As Long
Declare Function AddPrinterConnection Lib "winspool.drv" Alias "AddPrinterConnectionA" (ByVal pName As String) As Long
Declare Function DeletePrinterConnection Lib "winspool.drv" Alias "DeletePrinterConnectionA" (ByVal pName As String) As Long
Declare Function ConnectToPrinterDlg Lib "winspool.drv" Alias "ConnectToPrinterDlg" (ByVal hwnd As Long, ByVal flags As Long) As Long
Type PROVIDOR_INFO_1
pName As String
pEnvironment As String
pDLLName As String
End Type
Declare Function AddPrintProvidor Lib "winspool.drv" Alias "AddPrintProvidorA" (ByVal pName As String, ByVal Level As Long, pProvidorInfo As Byte) As Long
Declare Function DeletePrintProvidor Lib "winspool.drv" Alias "DeletePrintProvidorA" (ByVal pName As String, ByVal pEnvironment As String, ByVal pPrintProvidorName As String) As Long
Const SERVER_ACCESS_ADMINISTER = &H1
Const SERVER_ACCESS_ENUMERATE = &H2
Const PRINTER_ACCESS_ADMINISTER = &H4
Const PRINTER_ACCESS_USE = &H8
Const JOB_ACCESS_ADMINISTER = &H10
' Access rights for print servers
Const SERVER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SERVER_ACCESS_ADMINISTER Or SERVER_ACCESS_ENUMERATE)
Const SERVER_READ = (STANDARD_RIGHTS_READ Or SERVER_ACCESS_ENUMERATE)
Const SERVER_WRITE = (STANDARD_RIGHTS_WRITE Or SERVER_ACCESS_ADMINISTER Or SERVER_ACCESS_ENUMERATE)
Const SERVER_EXECUTE = (STANDARD_RIGHTS_EXECUTE Or SERVER_ACCESS_ENUMERATE)
' Access rights for printers
Const PRINTER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or PRINTER_ACCESS_ADMINISTER Or PRINTER_ACCESS_USE)
Const PRINTER_READ = (STANDARD_RIGHTS_READ Or PRINTER_ACCESS_USE)
Const PRINTER_WRITE = (STANDARD_RIGHTS_WRITE Or PRINTER_ACCESS_USE)
Const PRINTER_EXECUTE = (STANDARD_RIGHTS_EXECUTE Or PRINTER_ACCESS_USE)
' Access rights for jobs
Const JOB_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or JOB_ACCESS_ADMINISTER)
Const JOB_READ = (STANDARD_RIGHTS_READ Or JOB_ACCESS_ADMINISTER)
Const JOB_WRITE = (STANDARD_RIGHTS_WRITE Or JOB_ACCESS_ADMINISTER)
Const JOB_EXECUTE = (STANDARD_RIGHTS_EXECUTE Or JOB_ACCESS_ADMINISTER)
' Windows Network support
' RESOURCE ENUMERATION
Const RESOURCE_CONNECTED = &H1
Const RESOURCE_PUBLICNET = &H2
Const RESOURCE_REMEMBERED = &H3
Const RESOURCETYPE_ANY = &H0
Const RESOURCETYPE_DISK = &H1
Const RESOURCETYPE_PRINT = &H2
Const RESOURCETYPE_UNKNOWN = &HFFFF
Const RESOURCEUSAGE_CONNECTABLE = &H1
Const RESOURCEUSAGE_CONTAINER = &H2
Const RESOURCEUSAGE_RESERVED = &H80000000
Const RESOURCEDISPLAYTYPE_GENERIC = &H0
Const RESOURCEDISPLAYTYPE_DOMAIN = &H1
Const RESOURCEDISPLAYTYPE_SERVER = &H2
Const RESOURCEDISPLAYTYPE_SHARE = &H3
Const RESOURCEDISPLAYTYPE_FILE = &H4
Const RESOURCEDISPLAYTYPE_GROUP = &H5
Type NETRESOURCE
dwScope As Long
dwType As Long
dwDisplayType As Long
dwUsage As Long
lpLocalName As String
lpRemoteName As String
lpComment As String
lpProvider As String
End Type
Const CONNECT_UPDATE_PROFILE = &H1
Declare Function WNetAddConnection Lib "mpr.dll" Alias "WNetAddConnectionA" (ByVal lpszNetPath As String, ByVal lpszPassword As String, ByVal lpszLocalName As String) As Long
Declare Function WNetAddConnection2 Lib "mpr.dll" Alias "WNetAddConnection2A" (lpNetResource As NETRESOURCE, ByVal lpPassword As String, ByVal lpUserName As String, ByVal dwFlags As Long) As Long
Declare Function WNetCancelConnection Lib "mpr.dll" Alias "WNetCancelConnectionA" (ByVal lpszName As String, ByVal bForce As Long) As Long
Declare Function WNetCancelConnection2 Lib "mpr.dll" Alias "WNetCancelConnection2A" (ByVal lpName As String, ByVal dwFlags As Long, ByVal fForce As Long) As Long
Declare Function WNetGetConnection Lib "mpr.dll" Alias "WNetGetConnectionA" (ByVal lpszLocalName As String, ByVal lpszRemoteName As String, cbRemoteName As Long) As Long
Declare Function WNetOpenEnum Lib "mpr.dll" Alias "WNetOpenEnumA" (ByVal dwScope As Long, ByVal dwType As Long, ByVal dwUsage As Long, lpNetResource As NETRESOURCE, lphEnum As Long) As Long
Declare Function WNetEnumResource Lib "mpr.dll" Alias "WNetEnumResourceA" (ByVal hEnum As Long, lpcCount As Long, lpBuffer As Any, lpBufferSize As Long) As Long
Declare Function WNetCloseEnum Lib "mpr.dll" Alias "WNetCloseEnum" (ByVal hEnum As Long) As Long
Declare Function WNetGetUser Lib "mpr.dll" Alias "WNetGetUserA" (ByVal lpName As String, ByVal lpUserName As String, lpnLength As Long) As Long
Declare Function WNetConnectionDialog Lib "mpr.dll" Alias "WNetConnectionDialog" (ByVal hwnd As Long, ByVal dwType As Long) As Long
Declare Function WNetDisconnectDialog Lib "mpr.dll" Alias "WNetDisconnectDialog" (ByVal hwnd As Long, ByVal dwType As Long) As Long
Declare Function WNetGetLastError Lib "mpr.dll" Alias "WNetGetLastErrorA" (lpError As Long, ByVal lpErrorBuf As String, ByVal nErrorBufSize As Long, ByVal lpNameBuf As String, ByVal nNameBufSize As Long) As Long
' Status Codes
' This section is provided for backward compatibility. Use of the ERROR_
' codes is preferred. The WN_ error codes may not be available in future
Const NRC_LOCKFAIL = &H3C ' lock of user area failed
Const NRC_OPENERR = &H3F ' NETBIOS not loaded
Const NRC_SYSTEM = &H40 ' system error
Const NRC_PENDING = &HFF ' asynchronous command is not yet finished
'
' Win32 NetAPIs.
'
Declare Function NetUserChangePassword Lib "Netapi32.dll" (Domain As Any, User As Any, OldPass As Byte, NewPass As Byte) As Long
Declare Function NetUserGetInfo Lib "Netapi32.dll" (lpServer As Any, UserName As Byte, ByVal Level As Long, lpBuffer As Long) As Long
Declare Function NetUserGetGroups Lib "Netapi32.dll" (lpServer As Any, UserName As Byte, ByVal Level As Long, lpBuffer As Long, ByVal PrefMaxLen As Long, lpEntriesRead As Long, lpTotalEntries As Long) As Long
Declare Function NetUserGetLocalGroups Lib "Netapi32.dll" (lpServer As Any, UserName As Byte, ByVal Level As Long, ByVal Flags As Long, lpBuffer As Long, ByVal MaxLen As Long, lpEntriesRead As Long, lpTotalEntries As Long) As Long
Declare Function NetUserAdd Lib "netapi32" (lpServer As Any, ByVal Level As Long, lpUser As USER_INFO_3_API, lpError As Long) As Long
Declare Function NetWkstaGetInfo Lib "Netapi32.dll" (lpServer As Any, ByVal Level As Long, lpBuffer As Any) As Long
Declare Function NetWkstaUserGetInfo Lib "Netapi32.dll" (ByVal reserved As Any, ByVal Level As Long, lpBuffer As Any) As Long
Declare Function NetApiBufferFree Lib "Netapi32.dll" (ByVal lpBuffer As Long) As Long
Declare Function NetRemoteTOD Lib "Netapi32.dll" (yServer As Any, pBuffer As Long) As Long
Declare Function GetUserName Lib "advapi32.dll" Alias "GetUserNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Declare Function GetUserNameW Lib "advapi32.dll" (lpBuffer As Byte, nSize As Long) As Long
Declare Function GetComputerName Lib "kernel32" Alias "GetComputerNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Declare Function GetComputerNameW Lib "kernel32" (lpBuffer As Any, nSize As Long) As Long
Declare Function GetCurrentProcess Lib "kernel32" () As Long
Declare Function OpenProcessToken Lib "advapi32.dll" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long
Declare Function GetTokenInformation Lib "advapi32.dll" (ByVal TokenHandle As Long, ByVal TokenInformationClass As Long, TokenInformation As Any, ByVal TokenInformationLength As Long, ReturnLength As Long) As Long
Declare Function LookupAccountSid Lib "advapi32.dll" Alias "LookupAccountSidW" (ByVal lpSystemName As Any, Sid As Any, Name As Any, cbName As Long, ReferencedDomainName As Any, cbReferencedDomainName As Long, peUse As Integer) As Long
Declare Function NetLocalGroupDelMembers Lib "netapi32.dll" (ByVal psServer As Long, ByVal psLocalGroup As Long, ByVal lLevel As Long, uMember As LOCALGROUP_MEMBERS_INFO_0, ByVal lMemberCount As Long) As Long
Declare Function NetLocalGroupGetMembers Lib "netapi32.dll" (ByVal psServer As Long, ByVal psLocalGroup As Long, ByVal lLevel As Long, pBuffer As Long, ByVal lMaxLength As Long, plEntriesRead As Long, plTotalEntries As Long, phResume As Long) As Long
Declare Function WNetAddConnection2 Lib "mpr.dll" Alias "WNetAddConnection2A" (lpNetResource As NETRESOURCE, ByVal lpPassword As String, ByVal lpUserName As String, ByVal dwFlags As Long) As Long
Declare Function WNetOpenEnum Lib "mpr.dll" Alias "WNetOpenEnumA" (ByVal dwScope As Long, ByVal dwType As Long, ByVal dwUsage As Long, lpNetResource As Any, lphEnum As Long) As Long
Declare Function WNetEnumResource Lib "mpr.dll" Alias "WNetEnumResourceA" (ByVal hEnum As Long, lpcCount As Long, lpBuffer As NETRESOURCE, lpBufferSize As Long) As Long
Declare Function WNetCloseEnum Lib "mpr.dll" (ByVal hEnum As Long) As Long
Declare Function Netbios Lib "netapi32.dll" Alias "Netbios" (pncb As NCB) As Byte
Type USER_INFO_3
' Level 0 starts here
Name As Long
' Level 1 starts here
Password As Long
PasswordAge As Long
Privilege As Long
HomeDir As Long
Comment As Long
Flags As Long
ScriptPath As Long
' Level 2 starts here
AuthFlags As Long
FullName As Long
UserComment As Long
Parms As Long
Workstations As Long
LastLogon As Long
LastLogoff As Long
AcctExpires As Long
MaxStorage As Long
UnitsPerWeek As Long
LogonHours As Long
BadPwCount As Long
NumLogons As Long
LogonServer As Long
CountryCode As Long
CodePage As Long
' Level 3 starts here
UserID As Long
PrimaryGroupID As Long
Profile As Long
HomeDirDrive As Long
PasswordExpired As Long
End Type
Type GROUP_INFO_2
Name As Long
Comment As Long
GroupID As Long
Attributes As Long
End Type
Type LOCALGROUP_MEMBERS_INFO_0
pSID As Long
End Type
Type LOCALGROUP_MEMBERS_INFO_1
'Level 0 Starts Here
pSID As Long
'Level 1 Starts Here
eUsage As g_netSID_NAME_USE
psName As Long
End Type
Type WKSTA_INFO_102
wki102_platform_id As Long
wki102_computername As Long
wki102_langroup As Long
wki102_ver_major As Long
wki102_ver_minor As Long
wki102_lanroot As Long
wki102_logged_on_users As Long
End Type
Type WKSTA_USER_INFO_1
wkui1_username As Long
wkui1_logon_domain As Long
wkui1_oth_domains As Long
wkui1_logon_server As Long
End Type
Type NETRESOURCE
dwScope As Long
dwType As Long
dwDisplayType As Long
dwUsage As Long
pLocalName As Long
pRemoteName As Long
pComment As Long
pProvider As Long
End Type
Enum g_netSID_NAME_USE
SidTypeUser = 1&
SidTypeGroup = 2&
SidTypeDomain = 3&
SidTypeAlias = 4&
SidTypeWellKnownGroup = 5&
SidTypeDeletedAccount = 6&
SidTypeInvalid = 7&
SidTypeUnknown = 8&
End Enum
Const FILTER_TEMP_DUPLICATE_ACCOUNT As Long = &H1&
Const FILTER_NORMAL_ACCOUNT As Long = &H2&
Const FILTER_PROXY_ACCOUNT As Long = &H4&
Const FILTER_INTERDOMAIN_TRUST_ACCOUNT As Long = &H8&
Const FILTER_WORKSTATION_TRUST_ACCOUNT As Long = &H10&
' function prototypes, constants, and type definitions
' for Windows 32-bit Registry API
Const HKEY_CLASSES_ROOT = &H80000000
Const HKEY_CURRENT_USER = &H80000001
Const HKEY_LOCAL_MACHINE = &H80000002
Const HKEY_USERS = &H80000003
Const HKEY_PERFORMANCE_DATA = &H80000004
Const HKEY_CURRENT_CONFIG = &H80000005
Const HKEY_DYN_DATA = &H80000006
' Registry API prototypes
Declare Function RegCloseKey Lib "advapi32.dll" Alias "RegCloseKey" (ByVal hKey As Long) As Long
Declare Function RegConnectRegistry Lib "advapi32.dll" Alias "RegConnectRegistryA" (ByVal lpMachineName As String, ByVal hKey As Long, phkResult As Long) As Long
Declare Function RegCreateKey Lib "advapi32.dll" Alias "RegCreateKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, phkResult As Long) As Long
Declare Function RegCreateKeyEx Lib "advapi32.dll" Alias "RegCreateKeyExA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal Reserved As Long, ByVal lpClass As String, ByVal dwOptions As Long, ByVal samDesired As Long, lpSecurityAttributes As SECURITY_ATTRIBUTES, phkResult As Long, lpdwDisposition As Long) As Long
Declare Function RegDeleteKey Lib "advapi32.dll" Alias "RegDeleteKeyA" (ByVal hKey As Long, ByVal lpSubKey As String) As Long
Declare Function RegDeleteValue Lib "advapi32.dll" Alias "RegDeleteValueA" (ByVal hKey As Long, ByVal lpValueName As String) As Long
Declare Function RegEnumKey Lib "advapi32.dll" Alias "RegEnumKeyA" (ByVal hKey As Long, ByVal dwIndex As Long, ByVal lpName As String, ByVal cbName As Long) As Long
Declare Function RegEnumKeyEx Lib "advapi32.dll" Alias "RegEnumKeyExA" (ByVal hKey As Long, ByVal dwIndex As Long, ByVal lpName As String, lpcbName As Long, ByVal lpReserved As Long, ByVal lpClass As String, lpcbClass As Long, lpftLastWriteTime As FILETIME) As Long
Declare Function RegEnumValue Lib "advapi32.dll" Alias "RegEnumValueA" (ByVal hKey As Long, ByVal dwIndex As Long, ByVal lpValueName As String, lpcbValueName As Long, ByVal lpReserved As Long, lpType As Long, lpData As Byte, lpcbData As Long) As Long
Declare Function RegFlushKey Lib "advapi32.dll" Alias "RegFlushKey" (ByVal hKey As Long) As Long
Declare Function RegGetKeySecurity Lib "advapi32.dll" Alias "RegGetKeySecurity" (ByVal hKey As Long, ByVal SecurityInformation As Long, pSecurityDescriptor As SECURITY_DESCRIPTOR, lpcbSecurityDescriptor As Long) As Long
Declare Function RegLoadKey Lib "advapi32.dll" Alias "RegLoadKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal lpFile As String) As Long
Declare Function RegNotifyChangeKeyValue Lib "advapi32.dll" Alias "RegNotifyChangeKeyValue" (ByVal hKey As Long, ByVal bWatchSubtree As Long, ByVal dwNotifyFilter As Long, ByVal hEvent As Long, ByVal fAsynchronus As Long) As Long
Declare Function RegOpenKey Lib "advapi32.dll" Alias "RegOpenKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, phkResult As Long) As Long
Declare Function RegOpenKeyEx Lib "advapi32.dll" Alias "RegOpenKeyExA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal ulOptions As Long, ByVal samDesired As Long, phkResult As Long) As Long
Declare Function RegQueryInfoKey Lib "advapi32.dll" Alias "RegQueryInfoKeyA" (ByVal hKey As Long, ByVal lpClass As String, lpcbClass As Long, ByVal lpReserved As Long, lpcSubKeys As Long, lpcbMaxSubKeyLen As Long, lpcbMaxClassLen As Long, lpcValues As Long, lpcbMaxValueNameLen As Long, lpcbMaxValueLen As Long, lpcbSecurityDescriptor As Long, lpftLastWriteTime As FILETIME) As Long
Declare Function RegQueryValue Lib "advapi32.dll" Alias "RegQueryValueA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal lpValue As String, lpcbValue As Long) As Long
Declare Function RegQueryValueEx Lib "advapi32.dll" Alias "RegQueryValueExA" (ByVal hKey As Long, ByVal lpValueName As String, ByVal lpReserved As Long, lpType As Long, lpData As Any, lpcbData As Long) As Long ' Note that if you declare the lpData parameter as String, you must pass it By Value.
Declare Function RegReplaceKey Lib "advapi32.dll" Alias "RegReplaceKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal lpNewFile As String, ByVal lpOldFile As String) As Long
Declare Function RegRestoreKey Lib "advapi32.dll" Alias "RegRestoreKeyA" (ByVal hKey As Long, ByVal lpFile As String, ByVal dwFlags As Long) As Long
Declare Function RegSaveKey Lib "advapi32.dll" Alias "RegSaveKeyA" (ByVal hKey As Long, ByVal lpFile As String, lpSecurityAttributes As SECURITY_ATTRIBUTES) As Long
Declare Function RegSetKeySecurity Lib "advapi32.dll" Alias "RegSetKeySecurity" (ByVal hKey As Long, ByVal SecurityInformation As Long, pSecurityDescriptor As SECURITY_DESCRIPTOR) As Long
Declare Function RegSetValue Lib "advapi32.dll" Alias "RegSetValueA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal dwType As Long, ByVal lpData As String, ByVal cbData As Long) As Long
Declare Function RegSetValueEx Lib "advapi32.dll" Alias "RegSetValueExA" (ByVal hKey As Long, ByVal lpValueName As String, ByVal Reserved As Long, ByVal dwType As Long, lpData As Any, ByVal cbData As Long) As Long ' Note that if you declare the lpData parameter as String, you must pass it By Value.
Declare Function RegUnLoadKey Lib "advapi32.dll" Alias "RegUnLoadKeyA" (ByVal hKey As Long, ByVal lpSubKey As String) As Long
Declare Function InitiateSystemShutdown Lib "advapi32.dll" Alias "InitiateSystemShutdownA" (ByVal lpMachineName As String, ByVal lpMessage As String, ByVal dwTimeout As Long, ByVal bForceAppsClosed As Long, ByVal bRebootAfterShutdown As Long) As Long
Declare Function AbortSystemShutdown Lib "advapi32.dll" Alias "AbortSystemShutdownA" (ByVal lpMachineName As String) As Long
' Service database names
Const SERVICES_ACTIVE_DATABASE = "ServicesActive"
Const SERVICES_FAILED_DATABASE = "ServicesFailed"
' Value to indicate no change to an optional parameter
Const SERVICE_NO_CHANGE = &HFFFF
' Service State -- for Enum Requests (Bit Mask)
Const SERVICE_ACTIVE = &H1
Const SERVICE_INACTIVE = &H2
Const SERVICE_STATE_ALL = (SERVICE_ACTIVE Or SERVICE_INACTIVE)
' Controls
Const SERVICE_CONTROL_STOP = &H1
Const SERVICE_CONTROL_PAUSE = &H2
Const SERVICE_CONTROL_CONTINUE = &H3
Const SERVICE_CONTROL_INTERROGATE = &H4
Const SERVICE_CONTROL_SHUTDOWN = &H5
' Service State -- for CurrentState
Const SERVICE_STOPPED = &H1
Const SERVICE_START_PENDING = &H2
Const SERVICE_STOP_PENDING = &H3
Const SERVICE_RUNNING = &H4
Const SERVICE_CONTINUE_PENDING = &H5
Const SERVICE_PAUSE_PENDING = &H6
Const SERVICE_PAUSED = &H7
' Controls Accepted (Bit Mask)
Const SERVICE_ACCEPT_STOP = &H1
Const SERVICE_ACCEPT_PAUSE_CONTINUE = &H2
Const SERVICE_ACCEPT_SHUTDOWN = &H4
' Service Control Manager object specific access types
Const SC_MANAGER_CONNECT = &H1
Const SC_MANAGER_CREATE_SERVICE = &H2
Const SC_MANAGER_ENUMERATE_SERVICE = &H4
Const SC_MANAGER_LOCK = &H8
Const SC_MANAGER_QUERY_LOCK_STATUS = &H10
Const SC_MANAGER_MODIFY_BOOT_CONFIG = &H20
Const SC_MANAGER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SC_MANAGER_CONNECT Or SC_MANAGER_CREATE_SERVICE Or SC_MANAGER_ENUMERATE_SERVICE Or SC_MANAGER_LOCK Or SC_MANAGER_QUERY_LOCK_STATUS Or SC_MANAGER_MODIFY_BOOT_CONFIG)
' Service object specific access type
Const SERVICE_QUERY_CONFIG = &H1
Const SERVICE_CHANGE_CONFIG = &H2
Const SERVICE_QUERY_STATUS = &H4
Const SERVICE_ENUMERATE_DEPENDENTS = &H8
Const SERVICE_START = &H10
Const SERVICE_STOP = &H20
Const SERVICE_PAUSE_CONTINUE = &H40
Const SERVICE_INTERROGATE = &H80
Const SERVICE_USER_DEFINED_CONTROL = &H100
Const SERVICE_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SERVICE_QUERY_CONFIG Or SERVICE_CHANGE_CONFIG Or SERVICE_QUERY_STATUS Or SERVICE_ENUMERATE_DEPENDENTS Or SERVICE_START Or SERVICE_STOP Or SERVICE_PAUSE_CONTINUE Or SERVICE_INTERROGATE Or SERVICE_USER_DEFINED_CONTROL)
Type SERVICE_STATUS
dwServiceType As Long
dwCurrentState As Long
dwControlsAccepted As Long
dwWin32ExitCode As Long
dwServiceSpecificExitCode As Long
dwCheckPoint As Long
dwWaitHint As Long
End Type
Type ENUM_SERVICE_STATUS
lpServiceName As String
lpDisplayName As String
ServiceStatus As SERVICE_STATUS
End Type
Type QUERY_SERVICE_LOCK_STATUS
fIsLocked As Long
lpLockOwner As String
dwLockDuration As Long
End Type
Type QUERY_SERVICE_CONFIG
dwServiceType As Long
dwStartType As Long
dwErrorControl As Long
lpBinaryPathName As String
lpLoadOrderGroup As String
dwTagId As Long
lpDependencies As String
lpServiceStartName As String
lpDisplayName As String
End Type
Type SERVICE_TABLE_ENTRY
lpServiceName As String
lpServiceProc As Long
End Type
' ++ BUILD Version: 0010 ' Increment this if a change has global effects
' Copyright (c) 1995 Microsoft Corporation
' Module Name:
' winsvc.h
' Abstract:
' Header file for the Service Control Manager
' Environment:
' User Mode - Win32
' --*/
'
' Constants
' Character to designate that a name is a group
'
Const SC_GROUP_IDENTIFIER = "+"
' Prototype for the Service Control Handler Function
Declare Function ChangeServiceConfig Lib "advapi32.dll" Alias "ChangeServiceConfigA" (ByVal hService As Long, ByVal dwServiceType As Long, ByVal dwStartType As Long, ByVal dwErrorControl As Long, ByVal lpBinaryPathName As String, ByVal lpLoadOrderGroup As String, lpdwTagId As Long, ByVal lpDependencies As String, ByVal lpServiceStartName As String, ByVal lpPassword As String, ByVal lpDisplayName As String) As Long
Declare Function CloseServiceHandle Lib "advapi32.dll" Alias "CloseServiceHandle" (ByVal hSCObject As Long) As Long
Declare Function ControlService Lib "advapi32.dll" Alias "ControlService" (ByVal hService As Long, ByVal dwControl As Long, lpServiceStatus As SERVICE_STATUS) As Long
Declare Function CreateService Lib "advapi32.dll" Alias "CreateServiceA" (ByVal hSCManager As Long, ByVal lpServiceName As String, ByVal lpDisplayName As String, ByVal dwDesiredAccess As Long, ByVal dwServiceType As Long, ByVal dwStartType As Long, ByVal dwErrorControl As Long, ByVal lpBinaryPathName As String, ByVal lpLoadOrderGroup As String, lpdwTagId As Long, ByVal lpDependencies As String, ByVal lp As String, ByVal lpPassword As String) As Long
Declare Function DeleteService Lib "advapi32.dll" Alias "DeleteService" (ByVal hService As Long) As Long
Declare Function EnumDependentServices Lib "advapi32.dll" Alias "EnumDependentServicesA" (ByVal hService As Long, ByVal dwServiceState As Long, lpServices As ENUM_SERVICE_STATUS, ByVal cbBufSize As Long, pcbBytesNeeded As Long, lpServicesReturned As Long) As Long
Declare Function EnumServicesStatus Lib "advapi32.dll" Alias "EnumServicesStatusA" (ByVal hSCManager As Long, ByVal dwServiceType As Long, ByVal dwServiceState As Long, lpServices As ENUM_SERVICE_STATUS, ByVal cbBufSize As Long, pcbBytesNeeded As Long, lpServicesReturned As Long, lpResumeHandle As Long) As Long
Declare Function GetServiceKeyName Lib "advapi32.dll" Alias "GetServiceKeyNameA" (ByVal hSCManager As Long, ByVal lpDisplayName As String, ByVal lpServiceName As String, lpcchBuffer As Long) As Long
Declare Function GetServiceDisplayName Lib "advapi32.dll" Alias "GetServiceDisplayNameA" (ByVal hSCManager As Long, ByVal lpServiceName As String, ByVal lpDisplayName As String, lpcchBuffer As Long) As Long
Declare Function LockServiceDatabase Lib "advapi32.dll" Alias "LockServiceDatabase" (ByVal hSCManager As Long) As Long
Declare Function NotifyBootConfigStatus Lib "advapi32.dll" Alias "NotifyBootConfigStatus" (ByVal BootAcceptable As Long) As Long
Declare Function OpenSCManager Lib "advapi32.dll" Alias "OpenSCManagerA" (ByVal lpMachineName As String, ByVal lpDatabaseName As String, ByVal dwDesiredAccess As Long) As Long
Declare Function OpenService Lib "advapi32.dll" Alias "OpenServiceA" (ByVal hSCManager As Long, ByVal lpServiceName As String, ByVal dwDesiredAccess As Long) As Long
Declare Function QueryServiceConfig Lib "advapi32.dll" Alias "QueryServiceConfigA" (ByVal hService As Long, lpServiceConfig As QUERY_SERVICE_CONFIG, ByVal cbBufSize As Long, pcbBytesNeeded As Long) As Long
Declare Function QueryServiceLockStatus Lib "advapi32.dll" Alias "QueryServiceLockStatusA" (ByVal hSCManager As Long, lpLockStatus As QUERY_SERVICE_LOCK_STATUS, ByVal cbBufSize As Long, pcbBytesNeeded As Long) As Long
Declare Function QueryServiceObjectSecurity Lib "advapi32.dll" Alias "QueryServiceObjectSecurity" (ByVal hService As Long, ByVal dwSecurityInformation As Long, lpSecurityDescriptor As Any, ByVal cbBufSize As Long, pcbBytesNeeded As Long) As Long
Declare Function QueryServiceStatus Lib "advapi32.dll" Alias "QueryServiceStatus" (ByVal hService As Long, lpServiceStatus As SERVICE_STATUS) As Long
Declare Function RegisterServiceCtrlHandler Lib "advapi32.dll" Alias "RegisterServiceCtrlHandlerA" (ByVal lpServiceName As String, ByVal lpHandlerProc As Long) As Long
Declare Function SetServiceObjectSecurity Lib "advapi32.dll" Alias "SetServiceObjectSecurity" (ByVal hService As Long, ByVal dwSecurityInformation As Long, lpSecurityDescriptor As Any) As Long
Declare Function SetServiceStatus Lib "advapi32.dll" Alias "SetServiceStatus" (ByVal hServiceStatus As Long, lpServiceStatus As SERVICE_STATUS) As Long
Declare Function StartServiceCtrlDispatcher Lib "advapi32.dll" Alias "StartServiceCtrlDispatcherA" (lpServiceStartTable As SERVICE_TABLE_ENTRY) As Long
Declare Function StartService Lib "advapi32.dll" Alias "StartServiceA" (ByVal hService As Long, ByVal dwNumServiceArgs As Long, ByVal lpServiceArgVectors As Long) As Long
Declare Function UnlockServiceDatabase Lib "advapi32.dll" Alias "UnlockServiceDatabase" (ScLock As Any) As Long
Type LARGE_INTEGER
lowpart As Long
highpart As Long
End Type
' Section for Performance Monitor data
Const PERF_DATA_VERSION = 1
Const PERF_DATA_REVISION = 1
Type PERF_DATA_BLOCK
Signature As String * 4
LittleEndian As Long
Version As Long
Revision As Long
TotalByteLength As Long
HeaderLength As Long
NumObjectTypes As Long
DefaultObject As Long
SystemTime As SYSTEMTIME
PerfTime As LARGE_INTEGER
PerfFreq As LARGE_INTEGER
PerTime100nSec As LARGE_INTEGER
SystemNameLength As Long
SystemNameOffset As Long
End Type
Type PERF_OBJECT_TYPE
TotalByteLength As Long
DefinitionLength As Long
HeaderLength As Long
ObjectNameTitleIndex As Long
ObjectNameTitle As String
ObjectHelpTitleIndex As Long
ObjectHelpTitle As String
DetailLevel As Long
NumCounters As Long
DefaultCounter As Long
NumInstances As Long
CodePage As Long
PerfTime As LARGE_INTEGER
PerfFreq As LARGE_INTEGER
End Type
Const PERF_NO_INSTANCES = -1 ' no instances
' The counter type is the "or" of the following values as described below
'
' select one of the following to indicate the counter's data size
Const PERF_SIZE_DWORD = &H0
Const PERF_SIZE_LARGE = &H100
Const PERF_SIZE_ZERO = &H200 ' for Zero Length fields
Const PERF_SIZE_VARIABLE_LEN = &H300 ' length is in CounterLength field of Counter Definition struct
' select one of the following values to indicate the counter field usage
Const PERF_TYPE_NUMBER = &H0 ' a number (not a counter)
Const PERF_TYPE_COUNTER = &H400 ' an increasing numeric value
Const PERF_TYPE_TEXT = &H800 ' a text field
Const PERF_TYPE_ZERO = &HC00 ' displays a zero
' If the PERF_TYPE_NUMBER field was selected, then select one of the
' following to describe the Number
Const PERF_NUMBER_HEX = &H0 ' display as HEX value
Const PERF_NUMBER_DECIMAL = &H10000 ' display as a decimal integer
Const PERF_NUMBER_DEC_1000 = &H20000 ' display as a decimal/1000
'
' If the PERF_TYPE_COUNTER value was selected then select one of the
' following to indicate the type of counter
Const PERF_COUNTER_VALUE = &H0 ' display counter value
Const PERF_COUNTER_RATE = &H10000 ' divide ctr / delta time
Const PERF_COUNTER_FRACTION = &H20000 ' divide ctr / base
Const PERF_COUNTER_BASE = &H30000 ' base value used in fractions
Const PERF_COUNTER_ELAPSED = &H40000 ' subtract counter from current time
Const PERF_COUNTER_QUEUELEN = &H50000 ' Use Queuelen processing func.
Const PERF_COUNTER_HISTOGRAM = &H60000 ' Counter begins or ends a histogram
' If the PERF_TYPE_TEXT value was selected, then select one of the
' following to indicate the type of TEXT data.
Const PERF_TEXT_UNICODE = &H0 ' type of text in text field
Const PERF_TEXT_ASCII = &H10000 ' ASCII using the CodePage field
' Timer SubTypes
Const PERF_TIMER_TICK = &H0 ' use system perf. freq for base
Const PERF_TIMER_100NS = &H100000 ' use 100 NS timer time base units
Const PERF_OBJECT_TIMER = &H200000 ' use the object timer freq
' Any types that have calculations performed can use one or more of
' the following calculation modification flags listed here
Const PERF_DELTA_COUNTER = &H400000 ' compute difference first
Const PERF_DELTA_BASE = &H800000 ' compute base diff as well
Const PERF_INVERSE_COUNTER = &H1000000 ' show as 1.00-value (assumes:
Const PERF_MULTI_COUNTER = &H2000000 ' sum of multiple instances
' Select one of the following values to indicate the display suffix (if any)
Const PERF_DISPLAY_NO_SUFFIX = &H0 ' no suffix
Const PERF_DISPLAY_PER_SEC = &H10000000 ' "/sec"
Const PERF_DISPLAY_PERCENT = &H20000000 ' "%"
Const PERF_DISPLAY_SECONDS = &H30000000 ' "secs"
Const PERF_DISPLAY_NOSHOW = &H40000000 ' value is not displayed
Const PERF_COUNTER_COUNTER = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_TICK Or PERF_DELTA_COUNTER Or PERF_DISPLAY_PER_SEC)
Const PERF_COUNTER_TIMER = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_TICK Or PERF_DELTA_COUNTER Or PERF_DISPLAY_PERCENT)
' Queue Length Space-Time Product. Divide delta by delta time. No Display Suffix.
Const PERF_COUNTER_QUEUELEN_TYPE = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_QUEUELEN Or PERF_TIMER_TICK Or PERF_DELTA_COUNTER Or PERF_DISPLAY_NO_SUFFIX)
Const PERF_COUNTER_BULK_COUNT = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_TICK Or PERF_DELTA_COUNTER Or PERF_DISPLAY_PER_SEC)
' Indicates the counter is not a counter but rather Unicode text Display as text.
Const PERF_COUNTER_TEXT = (PERF_SIZE_VARIABLE_LEN Or PERF_TYPE_TEXT Or PERF_TEXT_UNICODE Or PERF_DISPLAY_NO_SUFFIX)
' Indicates the data is a counter which should not be
' time averaged on display (such as an error counter on a serial line)
' Display as is. No Display Suffix.
Const PERF_COUNTER_RAWCOUNT = (PERF_SIZE_DWORD Or PERF_TYPE_NUMBER Or PERF_NUMBER_DECIMAL Or PERF_DISPLAY_NO_SUFFIX)
' A count which is either 1 or 0 on each sampling interrupt (% busy)
' Divide delta by delta base. Display Suffix: "%"
Const PERF_SAMPLE_FRACTION = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_FRACTION Or PERF_DELTA_COUNTER Or PERF_DELTA_BASE Or PERF_DISPLAY_PERCENT)
' A count which is sampled on each sampling interrupt (queue length)
' Divide delta by delta time. No Display Suffix.
Const PERF_SAMPLE_COUNTER = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_TICK Or PERF_DELTA_COUNTER Or PERF_DISPLAY_NO_SUFFIX)
' A label: no data is associated with this counter (it has 0 length)
' Do not display.
Const PERF_COUNTER_NODATA = (PERF_SIZE_ZERO Or PERF_DISPLAY_NOSHOW)
' 64-bit Timer inverse (e.g., idle is measured, but display busy As Integer)
Const PERF_COUNTER_TIMER_INV = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_TICK Or PERF_DELTA_COUNTER Or PERF_INVERSE_COUNTER Or PERF_DISPLAY_PERCENT)
' The divisor for a sample, used with the previous counter to form a
' sampled %. You must check for >0 before dividing by this! This
' counter will directly follow the numerator counter. It should not
' be displayed to the user.
Const PERF_SAMPLE_BASE = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_BASE Or PERF_DISPLAY_NOSHOW Or &H1) ' for compatibility with pre-beta versions
' A timer which, when divided by an average base, produces a time
' in seconds which is the average time of some operation. This
' timer times total operations, and the base is the number of opera-
' tions. Display Suffix: "sec"
Const PERF_AVERAGE_TIMER = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_FRACTION Or PERF_DISPLAY_SECONDS)
' Used as the denominator in the computation of time or count
' averages. Must directly follow the numerator counter. Not dis-
' played to the user.
Const PERF_AVERAGE_BASE = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_BASE Or PERF_DISPLAY_NOSHOW Or &H2) ' for compatibility with pre-beta versions
' A bulk count which, when divided (typically) by the number of
' operations, gives (typically) the number of bytes per operation.
' No Display Suffix.
Const PERF_AVERAGE_BULK = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_FRACTION Or PERF_DISPLAY_NOSHOW)
' 64-bit Timer in 100 nsec units. Display delta divided by
' delta time. Display suffix: "%"
Const PERF_100NSEC_TIMER = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_100NS Or PERF_DELTA_COUNTER Or PERF_DISPLAY_PERCENT)
' 64-bit Timer inverse (e.g., idle is measured, but display busy As Integer)
Const PERF_100NSEC_TIMER_INV = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_100NS Or PERF_DELTA_COUNTER Or PERF_INVERSE_COUNTER Or PERF_DISPLAY_PERCENT)
' Timer for multiple instances, so result can exceed 100%.
Const PERF_COUNTER_MULTI_TIMER = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_DELTA_COUNTER Or PERF_TIMER_TICK Or PERF_MULTI_COUNTER Or PERF_DISPLAY_PERCENT)
' 64-bit Timer inverse (e.g., idle is measured, but display busy As Integer)
' Display 100 _MULTI_BASE - delta divided by delta time.
' Display suffix: "%" Timer for multiple instances, so result
' can exceed 100%. Followed by a counter of type _MULTI_BASE.
Const PERF_COUNTER_MULTI_TIMER_INV = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_RATE Or PERF_DELTA_COUNTER Or PERF_MULTI_COUNTER Or PERF_TIMER_TICK Or PERF_INVERSE_COUNTER Or PERF_DISPLAY_PERCENT)
' Number of instances to which the preceding _MULTI_..._INV counter
' applies. Used as a factor to get the percentage.
Const PERF_COUNTER_MULTI_BASE = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_BASE Or PERF_MULTI_COUNTER Or PERF_DISPLAY_NOSHOW)
' 64-bit Timer in 100 nsec units. Display delta divided by delta time.
' Display suffix: "%" Timer for multiple instances, so result can exceed 100%.
Const PERF_100NSEC_MULTI_TIMER = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_DELTA_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_100NS Or PERF_MULTI_COUNTER Or PERF_DISPLAY_PERCENT)
' 64-bit Timer inverse (e.g., idle is measured, but display busy As Integer)
' Display 100 _MULTI_BASE - delta divided by delta time.
' Display suffix: "%" Timer for multiple instances, so result
' can exceed 100%. Followed by a counter of type _MULTI_BASE.
Const PERF_100NSEC_MULTI_TIMER_INV = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_DELTA_COUNTER Or PERF_COUNTER_RATE Or PERF_TIMER_100NS Or PERF_MULTI_COUNTER Or PERF_INVERSE_COUNTER Or PERF_DISPLAY_PERCENT)
' Indicates the data is a fraction of the following counter which
' should not be time averaged on display (such as free space over
' total space.) Display as is. Display the quotient as "%".
Const PERF_RAW_FRACTION = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_FRACTION Or PERF_DISPLAY_PERCENT)
' Indicates the data is a base for the preceding counter which should
' not be time averaged on display (such as free space over total space.)
Const PERF_RAW_BASE = (PERF_SIZE_DWORD Or PERF_TYPE_COUNTER Or PERF_COUNTER_BASE Or PERF_DISPLAY_NOSHOW Or &H3) ' for compatibility with pre-beta versions
' The data collected in this counter is actually the start time of the
' item being measured. For display, this data is subtracted from the
' sample time to yield the elapsed time as the difference between the two.
' In the definition below, the PerfTime field of the Object contains
' the sample time as indicated by the PERF_OBJECT_TIMER bit and the
' difference is scaled by the PerfFreq of the Object to convert the time
' units into seconds.
Const PERF_ELAPSED_TIME = (PERF_SIZE_LARGE Or PERF_TYPE_COUNTER Or PERF_COUNTER_ELAPSED Or PERF_OBJECT_TIMER Or PERF_DISPLAY_SECONDS)
' The following counter type can be used with the preceding types to
' define a range of values to be displayed in a histogram.
Const PERF_COUNTER_HISTOGRAM_TYPE = &H80000000 ' Counter begins or ends a histogram
' The following are used to determine the level of detail associated
' with the counter. The user will be setting the level of detail
' that should be displayed at any given time.
Const PERF_DETAIL_NOVICE = 100 ' The uninformed can understand it
Const PERF_DETAIL_ADVANCED = 200 ' For the advanced user
Const PERF_DETAIL_EXPERT = 300 ' For the expert user
Const PERF_DETAIL_WIZARD = 400 ' For the system designer
Declare Function ImmInstallIME Lib "imm32.dll" Alias "ImmInstallIMEA" (ByVal lpszIMEFileName As String, ByVal lpszLayoutText As String) As Long
Declare Function ImmGetDefaultIMEWnd Lib "imm32.dll" Alias "ImmGetDefaultIMEWnd" (ByVal hwnd As Long) As Long
Declare Function ImmGetDescription Lib "imm32.dll" Alias "ImmGetDescriptionA" (ByVal hkl As Long, ByVal lpsz As String, ByVal uBufLen As Long) As Long
Declare Function ImmGetIMEFileName Lib "imm32.dll" Alias "ImmGetIMEFileNameA" (ByVal hkl As Long, ByVal lpStr As String, ByVal uBufLen As Long) As Long
Declare Function ImmGetProperty Lib "imm32.dll" Alias "ImmGetProperty" (ByVal hkl As Long, ByVal dw As Long) As Long
Declare Function ImmIsIME Lib "imm32.dll" Alias "ImmIsIME" (ByVal hkl As Long) As Long
Declare Function ImmSimulateHotKey Lib "imm32.dll" Alias "ImmSimulateHotKey" (ByVal hwnd As Long, ByVal dw As Long) As Long
Declare Function ImmCreateContext Lib "imm32.dll" Alias "ImmCreateContext" () As Long
Declare Function ImmDestroyContext Lib "imm32.dll" Alias "ImmDestroyContext" (ByVal himc As Long) As Long
Declare Function ImmGetContext Lib "imm32.dll" Alias "ImmGetContext" (ByVal hwnd As Long) As Long
Declare Function ImmReleaseContext Lib "imm32.dll" Alias "ImmReleaseContext" (ByVal hwnd As Long, ByVal himc As Long) As Long
Declare Function ImmAssociateContext Lib "imm32.dll" Alias "ImmAssociateContext" (ByVal hwnd As Long, ByVal himc As Long) As Long
Declare Function ImmGetCompositionString Lib "imm32.dll" Alias "ImmGetCompositionStringA" (ByVal himc As Long, ByVal dw As Long, lpv As Any, ByVal dw2 As Long) As Long
Declare Function ImmSetCompositionString Lib "imm32.dll" Alias "ImmSetCompositionStringA" (ByVal himc As Long, ByVal dwIndex As Long, lpComp As Any, ByVal dw As Long, lpRead As Any, ByVal dw2 As Long) As Long
Declare Function ImmGetCandidateListCount Lib "imm32.dll" Alias "ImmGetCandidateListCountA" (ByVal himc As Long, lpdwListCount As Long) As Long
Declare Function ImmGetCandidateList Lib "imm32.dll" Alias "ImmGetCandidateListA" (ByVal himc As Long, ByVal deIndex As Long, lpCandidateList As CANDIDATELIST, ByVal dwBufLen As Long) As Long
Declare Function ImmGetGuideLine Lib "imm32.dll" Alias " ImmGetGuideLineA" (ByVal himc As Long, ByVal dwIndex As Long, ByVal lpStr As String, ByVal dwBufLen As Long) As Long
Declare Function ImmGetConversionStatus Lib "imm32.dll" Alias "ImmGetConversionStatus" (ByVal himc As Long, lpdw As Long, lpdw2 As Long) As Long
Declare Function ImmSetConversionStatus Lib "imm32.dll" Alias "ImmSetConversionStatus" (ByVal himc As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
Declare Function ImmGetOpenStatus Lib "imm32.dll" Alias "ImmGetOpenStatus" (ByVal himc As Long) As Long
Declare Function ImmSetOpenStatus Lib "imm32.dll" Alias "ImmSetOpenStatus" (ByVal himc As Long, ByVal b As Long) As Long
Declare Function ImmGetCompositionFont Lib "imm32.dll" Alias "ImmGetCompositionFontA" (ByVal himc As Long, lpLogFont As LOGFONT) As Long
Declare Function ImmSetCompositionFont Lib "imm32.dll" Alias "ImmSetCompositionFontA" (ByVal himc As Long, lpLogFont As LOGFONT) As Long
Declare Function ImmConfigureIME Lib "imm32.dll" Alias "ImmConfigureIME" (ByVal hkl As Long, ByVal hwnd As Long, ByVal dw As Long) As Long
Declare Function ImmEscape Lib "imm32.dll" Alias "ImmEscapeA" (ByVal hkl As Long, ByVal himc As Long, ByVal un As Long, lpv As Any) As Long
Declare Function ImmGetConversionList Lib "imm32.dll" Alias "ImmGetConversionListA" (ByVal hkl As Long, ByVal himc As Long, ByVal lpsz As String, lpCandidateList As CANDIDATELIST, ByVal dwBufLen As Long, ByVal uFlag As Long) As Long
Declare Function ImmNotifyIME Lib "imm32.dll" Alias "ImmNotifyIME" (ByVal himc As Long, ByVal dwAction As Long, ByVal dwIndex As Long, ByVal dwValue As Long) As Long
Declare Function ImmGetStatusWindowPos Lib "imm32.dll" Alias "ImmGetStatusWindowPos" (ByVal himc As Long, lpPoint As POINTAPI) As Long
Declare Function ImmSetStatusWindowPos Lib "imm32.dll" Alias "ImmSetStatusWindowPos" (ByVal himc As Long, lpPoint As POINTAPI) As Long
Declare Function ImmGetCompositionWindow Lib "imm32.dll" Alias "ImmGetCompositionWindow" (ByVal himc As Long, lpCompositionForm As COMPOSITIONFORM) As Long
Declare Function ImmSetCompositionWindow Lib "imm32.dll" Alias "ImmSetCompositionWindow" (ByVal himc As Long, lpCompositionForm As COMPOSITIONFORM) As Long
Declare Function ImmGetCandidateWindow Lib "imm32.dll" Alias "ImmGetCandidateWindow" (ByVal himc As Long, ByVal dw As Long, lpCandidateForm As CANDIDATEFORM) As Long
Declare Function ImmSetCandidateWindow Lib "imm32.dll" Alias "ImmSetCandidateWindow" (ByVal himc As Long, lpCandidateForm As CANDIDATEFORM) As Long
Declare Function ImmIsUIMessage Lib "imm32.dll" Alias "ImmIsUIMessageA" (ByVal hwnd As Long, ByVal un As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function ImmGetVirtualKey Lib "imm32.dll" Alias "ImmGetVirtualKey" (ByVal hwnd As Long) As Long
Declare Function ImmRegisterWord Lib "imm32.dll" Alias "ImmRegisterWordA" (ByVal hkl As Long, ByVal lpszReading As String, ByVal dw As Long, ByVal lpszRegister As String) As Long
Declare Function ImmUnregisterWord Lib "imm32.dll" Alias "ImmUnregisterWordA" (ByVal hkl As Long, ByVal lpszReading As String, ByVal dw As Long, ByVal lpszUnregister As String) As Long
Declare Function ImmGetRegisterWordStyle Lib "imm32.dll" Alias " ImmGetRegisterWordStyleA" (ByVal hkl As Long, ByVal nItem As Long, lpStyleBuf As STYLEBUF) As Long
Declare Function ImmEnumRegisterWord Lib "imm32.dll" Alias "ImmEnumRegisterWordA" (ByVal hkl As Long, ByVal RegisterWordEnumProc As Long, ByVal lpszReading As String, ByVal dw As Long, ByVal lpszRegister As String, lpv As Any) As Long
' the IME related messages
Const WM_CONVERTREQUESTEX = &H108
Const WM_IME_STARTCOMPOSITION = &H10D
Const WM_IME_ENDCOMPOSITION = &H10E
Const WM_IME_COMPOSITION = &H10F
Const WM_IME_KEYLAST = &H10F
Const WM_IME_SETCONTEXT = &H281
Const WM_IME_NOTIFY = &H282
Const WM_IME_CONTROL = &H283
Const WM_IME_COMPOSITIONFULL = &H284
Const WM_IME_SELECT = &H285
Const WM_IME_CHAR = &H286
Const WM_IME_KEYDOWN = &H290
Const WM_IME_KEYUP = &H291
' wParam for WM_IME_CONTROL
Const IMC_GETCANDIDATEPOS = &H7
Const IMC_SETCANDIDATEPOS = &H8
Const IMC_GETCOMPOSITIONFONT = &H9
Const IMC_SETCOMPOSITIONFONT = &HA
Const IMC_GETCOMPOSITIONWINDOW = &HB
Const IMC_SETCOMPOSITIONWINDOW = &HC
Const IMC_GETSTATUSWINDOWPOS = &HF
Const IMC_SETSTATUSWINDOWPOS = &H10
Const IMC_CLOSESTATUSWINDOW = &H21
Const IMC_OPENSTATUSWINDOW = &H22
' wParam for WM_IME_CONTROL to the soft keyboard
' dwAction for ImmNotifyIME
Const NI_OPENCANDIDATE = &H10
Const NI_CLOSECANDIDATE = &H11
Const NI_SELECTCANDIDATESTR = &H12
Const NI_CHANGECANDIDATELIST = &H13
Const NI_FINALIZECONVERSIONRESULT = &H14
Const NI_COMPOSITIONSTR = &H15
Const NI_SETCANDIDATE_PAGESTART = &H16
Const NI_SETCANDIDATE_PAGESIZE = &H17
' lParam for WM_IME_SETCONTEXT
Const ISC_SHOWUICANDIDATEWINDOW = &H1
Const ISC_SHOWUICOMPOSITIONWINDOW = &H80000000
Const ISC_SHOWUIGUIDELINE = &H40000000
Const ISC_SHOWUIALLCANDIDATEWINDOW = &HF
Const ISC_SHOWUIALL = &HC000000F
' dwIndex for ImmNotifyIME/NI_COMPOSITIONSTR
Const CPS_COMPLETE = &H1
Const CPS_CONVERT = &H2
Const CPS_REVERT = &H3
Const CPS_CANCEL = &H4
' Windows for Simplified Chinese Edition hot key ID from 0x10 - 0x2F
Const IME_CHOTKEY_IME_NONIME_TOGGLE = &H10
Const IME_CHOTKEY_SHAPE_TOGGLE = &H11
Const IME_CHOTKEY_SYMBOL_TOGGLE = &H12
' Windows for Japanese Edition hot key ID from 0x30 - 0x4F
Const IME_JHOTKEY_CLOSE_OPEN = &H30
' Windows for Korean Edition hot key ID from 0x50 - 0x6F
Const IME_KHOTKEY_SHAPE_TOGGLE = &H50
Const IME_KHOTKEY_HANJACONVERT = &H51
Const IME_KHOTKEY_ENGLISH = &H52
' Windows for Tranditional Chinese Edition hot key ID from 0x70 - 0x8F
Const IME_THOTKEY_IME_NONIME_TOGGLE = &H70
Const IME_THOTKEY_SHAPE_TOGGLE = &H71
Const IME_THOTKEY_SYMBOL_TOGGLE = &H72
' direct switch hot key ID from 0x100 - 0x11F
Const IME_HOTKEY_DSWITCH_FIRST = &H100
Const IME_HOTKEY_DSWITCH_LAST = &H11F
' IME private hot key from 0x200 - 0x21F
Const IME_ITHOTKEY_RESEND_RESULTSTR = &H200
Const IME_ITHOTKEY_PREVIOUS_COMPOSITION = &H201
Const IME_ITHOTKEY_UISTYLE_TOGGLE = &H202
' parameter of ImmGetCompositionString
Const GCS_COMPREADSTR = &H1
Const GCS_COMPREADATTR = &H2
Const GCS_COMPREADCLAUSE = &H4
Const GCS_COMPSTR = &H8
Const GCS_COMPATTR = &H10
Const GCS_COMPCLAUSE = &H20
Const GCS_CURSORPOS = &H80
Const GCS_DELTASTART = &H100
Const GCS_RESULTREADSTR = &H200
Const GCS_RESULTREADCLAUSE = &H400
Const GCS_RESULTSTR = &H800
Const GCS_RESULTCLAUSE = &H1000
' style bit flags for WM_IME_COMPOSITION
Const CS_INSERTCHAR = &H2000
Const CS_NOMOVECARET = &H4000
' bits of fdwInit of INPUTCONTEXT
' IME property bits
Const IME_PROP_AT_CARET = &H10000
Const IME_PROP_SPECIAL_UI = &H20000
Const IME_PROP_CANDLIST_START_FROM_1 = &H40000
Const IME_PROP_UNICODE = &H80000
' IME UICapability bits
Const UI_CAP_2700 = &H1
Const UI_CAP_ROT90 = &H2
Const UI_CAP_ROTANY = &H4
' ImmSetCompositionString Capability bits
Const SCS_CAP_COMPSTR = &H1
Const SCS_CAP_MAKEREAD = &H2
' IME WM_IME_SELECT inheritance Capability bits
Const SELECT_CAP_CONVERSION = &H1
Const SELECT_CAP_SENTENCE = &H2
' ID for deIndex of ImmGetGuideLine
Const GGL_LEVEL = &H1
Const GGL_INDEX = &H2
Const GGL_STRING = &H3
Const GGL_PRIVATE = &H4
' ID for dwLevel of GUIDELINE Structure
Const GL_LEVEL_NOGUIDELINE = &H0
Const GL_LEVEL_FATAL = &H1
Const GL_LEVEL_ERROR = &H2
Const GL_LEVEL_WARNING = &H3
Const GL_LEVEL_INFORMATION = &H4
' ID for dwIndex of GUIDELINE Structure
Const GL_ID_UNKNOWN = &H0
Const GL_ID_NOMODULE = &H1
Const GL_ID_NODICTIONARY = &H10
Const GL_ID_CANNOTSAVE = &H11
Const GL_ID_NOCONVERT = &H20
Const GL_ID_TYPINGERROR = &H21
Const GL_ID_TOOMANYSTROKE = &H22
Const GL_ID_READINGCONFLICT = &H23
Const GL_ID_INPUTREADING = &H24
Const GL_ID_INPUTRADICAL = &H25
Const GL_ID_INPUTCODE = &H26
Const GL_ID_INPUTSYMBOL = &H27
Const GL_ID_CHOOSECANDIDATE = &H28
Const GL_ID_REVERSECONVERSION = &H29
Const GL_ID_PRIVATE_FIRST = &H8000
Const GL_ID_PRIVATE_LAST = &HFFFF
' ID for dwIndex of ImmGetProperty
Const IGP_PROPERTY = &H4
Const IGP_CONVERSION = &H8
Const IGP_SENTENCE = &HC
Const IGP_UI = &H10
Const IGP_SETCOMPSTR = &H14
Const IGP_SELECT = &H18
' dwIndex for ImmSetCompositionString API
Const SCS_SETSTR = (GCS_COMPREADSTR Or GCS_COMPSTR)
Const SCS_CHANGEATTR = (GCS_COMPREADATTR Or GCS_COMPATTR)
Const SCS_CHANGECLAUSE = (GCS_COMPREADCLAUSE Or GCS_COMPCLAUSE)
' attribute for COMPOSITIONSTRING Structure
Const ATTR_INPUT = &H0
Const ATTR_TARGET_CONVERTED = &H1
Const ATTR_CONVERTED = &H2
Const ATTR_TARGET_NOTCONVERTED = &H3
Const ATTR_INPUT_ERROR = &H4
' bit field for IMC_SETCOMPOSITIONWINDOW, IMC_SETCANDIDATEWINDOW
Const CFS_DEFAULT = &H0
Const CFS_RECT = &H1
Const CFS_POINT = &H2
Const CFS_SCREEN = &H4
Const CFS_FORCE_POSITION = &H20
Const CFS_CANDIDATEPOS = &H40
Const CFS_EXCLUDE = &H80
' conversion direction for ImmGetConversionList
Const GCL_CONVERSION = &H1
Const GCL_REVERSECONVERSION = &H2
Const GCL_REVERSE_LENGTH = &H3
' bit field for conversion mode
Const IME_CMODE_ALPHANUMERIC = &H0
Const IME_CMODE_NATIVE = &H1
Const IME_CMODE_CHINESE = IME_CMODE_NATIVE
Const IME_CMODE_HANGEUL = IME_CMODE_NATIVE
Const IME_CMODE_JAPANESE = IME_CMODE_NATIVE
Const IME_CMODE_KATAKANA = &H2 ' only effect under IME_CMODE_NATIVE
Declare Function DragQueryFile Lib "shell32.dll" Alias "DragQueryFileA" (ByVal HDROP As Long, ByVal UINT As Long, ByVal lpStr As String, ByVal ch As Long) As Long
Declare Function DragQueryPoint Lib "shell32.dll" Alias "DragQueryPoint" (ByVal HDROP As Long, lpPoint As POINTAPI) As Long
Declare Sub DragFinish Lib "shell32.dll" Alias "DragFinish" (ByVal hDrop As Long)
Declare Sub DragAcceptFiles Lib "shell32.dll" Alias "DragAcceptFiles" (ByVal hwnd As Long, ByVal fAccept As Long)
Declare Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" (ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As Long
Declare Function FindExecutable Lib "shell32.dll" Alias "FindExecutableA" (ByVal lpFile As String, ByVal lpDirectory As String, ByVal lpResult As String) As Long
Declare Function ShellAbout Lib "shell32.dll" Alias "ShellAboutA" (ByVal hwnd As Long, ByVal szApp As String, ByVal szOtherStuff As String, ByVal hIcon As Long) As Long
Declare Function DuplicateIcon Lib "shell32.dll" Alias "DuplicateIcon" (ByVal hInst As Long, ByVal hIcon As Long) As Long
Declare Function ExtractAssociatedIcon Lib "shell32.dll" Alias "ExtractAssociateIconA" (ByVal hInst As Long, ByVal lpIconPath As String, lpiIcon As Long) As Long
Declare Function ExtractIcon Lib "shell32.dll" Alias "ExtractIconA" (ByVal hInst As Long, ByVal lpszExeFileName As String, ByVal nIconIndex As Long) As Long
Type DRAGINFO
uSize As Long ' init with sizeof(DRAGINFO)
pt As POINTAPI
fNC As Long
lpFileList As String
grfKeyState As Long
End Type
' // AppBar stuff
Const ABM_NEW = &H0
Const ABM_REMOVE = &H1
Const ABM_QUERYPOS = &H2
Const ABM_SETPOS = &H3
Const ABM_GETSTATE = &H4
Const ABM_GETTASKBARPOS = &H5
Const ABM_ACTIVATE = &H6 ' lParam == TRUE/FALSE means activate/deactivate
Const ABM_GETAUTOHIDEBAR = &H7
Const ABM_SETAUTOHIDEBAR = &H8 ' this can fail at any time. MUST check the result
' lParam = TRUE/FALSE Set/Unset
' uEdge = what edge
Const ABM_WINDOWPOSCHANGED = &H9
' these are put in the wparam of callback messages
Const ABN_STATECHANGE = &H0
Const ABN_POSCHANGED = &H1
Const ABN_FULLSCREENAPP = &H2
Const ABN_WINDOWARRANGE = &H3 ' lParam == TRUE means hide
' flags for get state
Const ABS_AUTOHIDE = &H1
Const ABS_ALWAYSONTOP = &H2
Const ABE_LEFT = 0
Const ABE_TOP = 1
Const ABE_RIGHT = 2
Const ABE_BOTTOM = 3
Type APPBARDATA
cbSize As Long
hwnd As Long
uCallbackMessage As Long
uEdge As Long
rc As Rect
lParam As Long ' message specific
End Type
Declare Function SHAppBarMessage Lib "shell32.dll" Alias "SHAppBarMessage" (ByVal dwMessage As Long, pData As APPBARDATA) As Long
' // EndAppBar
Declare Function DoEnvironmentSubst Lib "shell32.dll" Alias "DoEnvironmentSubstA" (ByVal szString As String, ByVal cbString As Long) As Long
Declare Function FindEnvironmentString Lib "shell32.dll" Alias "FindEnvironmentStringA" (ByVal szEnvVar As String) As String
Const EIRESID = -1
Declare Function ExtractIconEx Lib "shell32.dll" Alias "ExtractIconExA" (ByVal lpszFile As String, ByVal nIconIndex As Long, phiconLarge As Long, phiconSmall As Long, ByVal nIcons As Long) As Long
Const FOF_NOCONFIRMATION = &H10 ' Don't prompt the user.
Const FOF_WANTMAPPINGHANDLE = &H20 ' Fill in SHFILEOPSTRUCT.hNameMappings
' Must be freed using SHFreeNameMappings
Const FOF_ALLOWUNDO = &H40
Const FOF_FILESONLY = &H80 ' on *.*, do only files
Const FOF_SIMPLEPROGRESS = &H100 ' means don't show names of files
Const FOF_NOCONFIRMMKDIR = &H200 ' don't confirm making any needed dirs
Const PO_DELETE = &H13 ' printer is being deleted
Const PO_RENAME = &H14 ' printer is being renamed
Const PO_PORTCHANGE = &H20 ' port this printer connected to is being changed
' if this id is set, the strings received by
' the copyhook are a doubly-null terminated
' list of strings. The first is the printer
' name and the second is the printer port.
Const PO_REN_PORT = &H34 ' PO_RENAME and PO_PORTCHANGE at same time.
' no POF_ flags currently defined
' implicit parameters are:
' if pFrom or pTo are unqualified names the current directories are
' taken from the global current drive/directory settings managed
' by Get/SetCurrentDrive/Directory
'
' the global confirmation settings
Type SHFILEOPSTRUCT
hwnd As Long
wFunc As Long
pFrom As String
pTo As String
fFlags As Integer
fAnyOperationsAborted As Long
hNameMappings As Long
lpszProgressTitle As String ' only used if FOF_SIMPLEPROGRESS
End Type
Declare Function SHFileOperation Lib "shell32.dll" Alias " SHFileOperationA" (lpFileOp As SHFILEOPSTRUCT) As Long
Declare Sub SHFreeNameMappings Lib "shell32.dll" Alias "SHFreeNameMappings" (ByVal hNameMappings As Long)
Type SHNAMEMAPPING
pszOldPath As String
pszNewPath As String
cchOldPath As Long
cchNewPath As Long
End Type
' // End Shell File Operations
' // Begin ShellExecuteEx and family
' ShellExecute() and ShellExecuteEx() error codes
' regular WinExec() codes
Const SE_ERR_FNF = 2 ' file not found
Const SE_ERR_PNF = 3 ' path not found
Const SE_ERR_ACCESSDENIED = 5 ' access denied
Const SE_ERR_OOM = 8 ' out of memory
Const SE_ERR_DLLNOTFOUND = 32
' Note CLASSKEY overrides CLASSNAME
Const SEE_MASK_CLASSNAME = &H1
Const SEE_MASK_CLASSKEY = &H3
' Note INVOKEIDLIST overrides IDLIST
Const SEE_MASK_IDLIST = &H4
Const SEE_MASK_INVOKEIDLIST = &HC
Const SEE_MASK_ICON = &H10
Const SEE_MASK_HOTKEY = &H20
Const SEE_MASK_NOCLOSEPROCESS = &H40
Const SEE_MASK_CONNECTNETDRV = &H80
Const SEE_MASK_FLAG_DDEWAIT = &H100
Const SEE_MASK_DOENVSUBST = &H200
Const SEE_MASK_FLAG_NO_UI = &H400
Type SHELLEXECUTEINFO
cbSize As Long
fMask As Long
hwnd As Long
lpVerb As String
lpFile As String
lpParameters As String
lpDirectory As String
nShow As Long
hInstApp As Long
' Optional fields
lpIDList As Long
lpClass As String
hkeyClass As Long
dwHotKey As Long
hIcon As Long
hProcess As Long
End Type
Declare Sub WinExecError Lib "shell32.dll" Alias "WinExecErrorA" (ByVal hwnd As Long, ByVal error As Long, ByVal lpstrFileName As String, ByVal lpstrTitle As String)
' // End ShellExecuteEx and family
' // Tray notification definitions
Type NOTIFYICONDATA
cbSize As Long
hwnd As Long
uID As Long
uFlags As Long
uCallbackMessage As Long
hIcon As Long
szTip As String * 64
End Type
Const NIM_ADD = &H0
Const NIM_MODIFY = &H1
Const NIM_DELETE = &H2
Const NIF_MESSAGE = &H1
Const NIF_ICON = &H2
Const NIF_TIP = &H4
Declare Function Shell_NotifyIcon Lib "shell32.dll" Alias " Shell_NotifyIconA" (ByVal dwMessage As Long, lpData As NOTIFYICONDATA) As Long
' // End Tray Notification Icons
' // Begin SHGetFileInfo
' * The SHGetFileInfo API provides an easy way to get attributes
' * for a file given a pathname.
' *
' * PARAMETERS
' *
' * pszPath file name to get info about
' * dwFileAttributes file attribs, only used with SHGFI_USEFILEATTRIBUTES
' * psfi place to return file info
' * cbFileInfo size of structure
' * uFlags flags
' *
' * RETURN
' * TRUE if things worked
' */
Type SHFILEINFO
hIcon As Long ' out: icon
iIcon As Long ' out: icon index
dwAttributes As Long ' out: SFGAO_ flags
szDisplayName As String * MAX_PATH ' out: display name (or path)
szTypeName As String * 80 ' out: type name
End Type
Const SHGFI_ICON = &H100 ' get icon
Const SHGFI_DISPLAYNAME = &H200 ' get display name
Const SHGFI_TYPENAME = &H400 ' get type name
Const SHGFI_ATTRIBUTES = &H800 ' get attributes
Const SHGFI_ICONLOCATION = &H1000 ' get icon location
Const SHGFI_EXETYPE = &H2000 ' return exe type
Const SHGFI_SYSICONINDEX = &H4000 ' get system icon index
Const SHGFI_LINKOVERLAY = &H8000 ' put a link overlay on icon
Const SHGFI_SELECTED = &H10000 ' show icon in selected state
Const SHGFI_LARGEICON = &H0 ' get large icon
Const SHGFI_SMALLICON = &H1 ' get small icon
Const SHGFI_OPENICON = &H2 ' get open icon
Const SHGFI_SHELLICONSIZE = &H4 ' get shell size icon
Const SHGFI_PIDL = &H8 ' pszPath is a pidl
Const SHGFI_USEFILEATTRIBUTES = &H10 ' use passed dwFileAttribute
Declare Function SHGetFileInfo Lib "shell32.dll" Alias "SHGetFileInfoA" (ByVal pszPath As String, ByVal dwFileAttributes As Long, psfi As SHFILEINFO, ByVal cbFileInfo As Long, ByVal uFlags As Long) As Long
Declare Function SHGetNewLinkInfo Lib "shell32.dll" Alias "SHGetNewLinkInfoA" (ByVal pszLinkto As String, ByVal pszDir As String, ByVal pszName As String, pfMustCopy As Long, ByVal uFlags As Long) As Long
Const SHGNLI_PIDL = &H1 ' pszLinkTo is a pidl
Const SHGNLI_PREFIXNAME = &H2 ' Make name "Shortcut to xxx"
' // End SHGetFileInfo
' Copyright (C) 1993 - 1995 Microsoft Corporation
' Module Name:
' winperf.h
' Abstract:
' Header file for the Performance Monitor data.
' This file contains the definitions of the data structures returned
' by the Configuration Registry in response to a request for
' performance data. This file is used by both the Configuration
' Registry and the Performance Monitor to define their interface.
' The complete interface is described here, except for the name
' of the node to query in the registry. It is
' HKEY_PERFORMANCE_DATA.
' By querying that node with a subkey of "Global" the caller will
' retrieve the structures described here.
' There is no need to RegOpenKey() the reserved handle HKEY_PERFORMANCE_DATA,
' but the caller should RegCloseKey() the handle so that network transports
' and drivers can be removed or installed (which cannot happen while
' they are open for monitoring.) Remote requests must first
' RegConnectRegistry().
' --*/
' Data structure definitions.
' In order for data to be returned through the Configuration Registry
' in a system-independent fashion, it must be self-describing.
' In the following, all offsets are in bytes.
'
' Data is returned through the Configuration Registry in a
' a data block which begins with a _PERF_DATA_BLOCK structure.
'
' The _PERF_DATA_BLOCK structure is followed by NumObjectTypes of
' data sections, one for each type of object measured. Each object
' type section begins with a _PERF_OBJECT_TYPE structure.
' ----- VS_VERSION.dwFileSubtype for VFT_WINDOWS_DRV -----
Const VFT2_UNKNOWN = &H0&
Const VFT2_DRV_PRINTER = &H1&
Const VFT2_DRV_KEYBOARD = &H2&
Const VFT2_DRV_LANGUAGE = &H3&
Const VFT2_DRV_DISPLAY = &H4&
Const VFT2_DRV_MOUSE = &H5&
Const VFT2_DRV_NETWORK = &H6&
Const VFT2_DRV_SYSTEM = &H7&
Const VFT2_DRV_INSTALLABLE = &H8&
Const VFT2_DRV_SOUND = &H9&
Const VFT2_DRV_COMM = &HA&
Const VFT2_DRV_INPUTMETHOD = &HB&
' ----- VS_VERSION.dwFileSubtype for VFT_WINDOWS_FONT -----
Const VFT2_FONT_RASTER = &H1&
Const VFT2_FONT_VECTOR = &H2&
Const VFT2_FONT_TRUETYPE = &H3&
' ----- VerFindFile() flags -----
Const VFFF_ISSHAREDFILE = &H1
Const VFF_CURNEDEST = &H1
Const VFF_FILEINUSE = &H2
Const VFF_BUFFTOOSMALL = &H4
' ----- VerInstallFile() flags -----
Const VIFF_FORCEINSTALL = &H1
Const VIFF_DONTDELETEOLD = &H2
Const VIF_TEMPFILE = &H1&
Const VIF_MISMATCH = &H2&
Const VIF_SRCOLD = &H4&
Const VIF_DIFFLANG = &H8&
Const VIF_DIFFCODEPG = &H10&
Const VIF_DIFFTYPE = &H20&
Const VIF_WRITEPROT = &H40&
Const VIF_FILEINUSE = &H80&
Const VIF_OUTOFSPACE = &H100&
Const VIF_ACCESSVIOLATION = &H200&
Const VIF_SHARINGVIOLATION = &H400&
Const VIF_CANNOTCREATE = &H800&
Const VIF_CANNOTDELETE = &H1000&
Const VIF_CANNOTRENAME = &H2000&
Const VIF_CANNOTDELETECUR = &H4000&
Const VIF_OUTOFMEMORY = &H8000&
Const VIF_CANNOTREADSRC = &H10000
Const VIF_CANNOTREADDST = &H20000
Const VIF_BUFFTOOSMALL = &H40000
' ----- Types and structures -----
Type VS_FIXEDFILEINFO
dwSignature As Long
dwStrucVersion As Long ' e.g. 0x00000042 = "0.42"
dwFileVersionMS As Long ' e.g. 0x00030075 = "3.75"
dwFileVersionLS As Long ' e.g. 0x00000031 = "0.31"
dwProductVersionMS As Long ' e.g. 0x00030010 = "3.10"
dwProductVersionLS As Long ' e.g. 0x00000031 = "0.31"
dwFileFlagsMask As Long ' = 0x3F for version "0.42"
dwFileFlags As Long ' e.g. VFF_DEBUG Or VFF_PRERELEASE
dwFileOS As Long ' e.g. VOS_DOS_WINDOWS16
dwFileType As Long ' e.g. VFT_DRIVER
dwFileSubtype As Long ' e.g. VFT2_DRV_KEYBOARD
dwFileDateMS As Long ' e.g. 0
dwFileDateLS As Long ' e.g. 0
End Type
' ----- Function prototypes -----
Declare Function VerFindFile Lib "version.dll" Alias "VerFindFileA" (ByVal uFlags As Long, ByVal szFileName As String, ByVal szWinDir As String, ByVal szAppDir As String, ByVal szCurDir As String, lpuCurDirLen As Long, ByVal szDestDir As String, lpuDestDirLen As Long) As Long
Declare Function VerInstallFile Lib "version.dll" Alias " VerInstallFileA" (ByVal uFlags As Long, ByVal szSrcFileName As String, ByVal szDestFileName As String, ByVal szSrcDir As String, ByVal szDestDir As String, ByVal szCurDir As String, ByVal szTmpFile As String, lpuTmpFileLen As Long) As Long
' Returns size of version info in Bytes
Declare Function GetFileVersionInfoSize Lib "version.dll" Alias "GetFileVersionInfoSizeA" (ByVal lptstrFilename As String, lpdwHandle As Long) As Long
' Read version info into buffer
' /* Length of buffer for info *
' /* Information from GetFileVersionSize *
' /* Filename of version stamped file *
Declare Function GetFileVersionInfo Lib "version.dll" Alias "GetFileVersionInfoA" (ByVal lptstrFilename As String, ByVal dwHandle As Long, ByVal dwLen As Long, lpData As Any) As Long
Declare Function VerLanguageName Lib "kernel32" Alias "VerLanguageNameA" (ByVal wLang As Long, ByVal szLang As String, ByVal nSize As Long) As Long
Declare Function VerQueryValue Lib "version.dll" Alias "VerQueryValue" (pBlock As Any, ByVal lpSubBlock As String, ByVal lplpBuffer As Long, puLen As Long) As Long
' Define API decoration for direct importing of DLL references.
Declare Function HeapValidate Lib "kernel32" Alias "HeapValidate" (ByVal hHeap As Long, ByVal dwFlags As Long, lpMem As Any) As Long
Declare Function HeapCompact Lib "kernel32" Alias "HeapCompact" (ByVal hHeap As Long, ByVal dwFlags As Long) As Long
Const PROCESS_HEAP_REGION = &H1
Const PROCESS_HEAP_UNCOMMITTED_RANGE = &H2
Const PROCESS_HEAP_ENTRY_BUSY = &H4
Const PROCESS_HEAP_ENTRY_MOVEABLE = &H10
Const PROCESS_HEAP_ENTRY_DDESHARE = &H20
Declare Function HeapLock Lib "kernel32" Alias "HeapLock" (ByVal hHeap As Long) As Long
Declare Function HeapUnlock Lib "kernel32" Alias "HeapUnlock" (ByVal hHeap As Long) As Long
' GetBinaryType return values.
Const SCS_32BIT_BINARY = 0
Const SCS_DOS_BINARY = 1
Const SCS_WOW_BINARY = 2
Const SCS_PIF_BINARY = 3
Const SCS_POSIX_BINARY = 4
Const SCS_OS216_BINARY = 5
Declare Function GetBinaryType Lib "kernel32" Alias "GetBinaryTypeA" (ByVal lpApplicationName As String, lpBinaryType As Long) As Long
Declare Function GetShortPathName Lib "kernel32" Alias "GetShortPathNameA" (ByVal lpszLongPath As String, ByVal lpszShortPath As String, ByVal cchBuffer As Long) As Long
Declare Function GetProcessAffinityMask Lib "kernel32" Alias "GetProcessAffinityMask" (ByVal hProcess As Long, lpProcessAffinityMask As Long, SystemAffinityMask As Long) As Long
' Logon Support APIs
Const LOGON32_LOGON_INTERACTIVE = 2
Const LOGON32_LOGON_BATCH = 4
Const LOGON32_LOGON_SERVICE = 5
Const LOGON32_PROVIDER_DEFAULT = 0
Const LOGON32_PROVIDER_WINNT35 = 1
Declare Function LogonUser Lib "kernel32" Alias "LogonUserA" (ByVal lpszUsername As String, ByVal lpszDomain As String, ByVal lpszPassword As String, ByVal dwLogonType As Long, ByVal dwLogonProvider As Long, phToken As Long) As Long
Declare Function ImpersonateLoggedOnUser Lib "kernel32" Alias "ImpersonateLoggedOnUser" (ByVal hToken As Long) As Long
Declare Function CreateProcessAsUser Lib "advapi32.dll" Alias "CreateProcessAsUserA" (ByVal hToken As Long, ByVal lpApplicationName As String, ByVal lpCommandLine As String, ByVal lpProcessAttributes As SECURITY_ATTRIBUTES, ByVal lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, ByVal lpEnvironment As String, ByVal lpCurrentDirectory As String, ByVal lpStartupInfo As STARTUPINFO, ByVal lpProcessInformation As PROCESS_INFORMATION) As Long
' Performance counter API's
Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type
' dwPlatformId defines:
'
Const VER_PLATFORM_WIN32s = 0
Const VER_PLATFORM_WIN32_WINDOWS = 1
Const VER_PLATFORM_WIN32_NT = 2
Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long
' Power Management APIs
Const AC_LINE_OFFLINE = &H0
Const AC_LINE_ONLINE = &H1
Const AC_LINE_BACKUP_POWER = &H2
Const AC_LINE_UNKNOWN = &HFF
Const BATTERY_FLAG_HIGH = &H1
Const BATTERY_FLAG_LOW = &H2
Const BATTERY_FLAG_CRITICAL = &H4
Const BATTERY_FLAG_CHARGING = &H8
Const BATTERY_FLAG_NO_BATTERY = &H80
Const BATTERY_FLAG_UNKNOWN = &HFF
Const BATTERY_PERCENTAGE_UNKNOWN = &HFF
Const BATTERY_LIFE_UNKNOWN = &HFFFF
Type SYSTEM_POWER_STATUS
ACLineStatus As Byte
BatteryFlag As Byte
BatteryLifePercent As Byte
Reserved1 As Byte
BatteryLifeTime As Long
BatteryFullLifeTime As Long
End Type
Declare Function GetSystemPowerStatus Lib "kernel32" Alias "GetSystemPowerStatus" (lpSystemPowerStatus As SYSTEM_POWER_STATUS) As Long
Declare Function SetSystemPowerState Lib "kernel32" Alias "SetSystemPowerState" (ByVal fSuspend As Long, ByVal fForce As Long) As Long
' * commdlg.h -- This module defines the 32-Bit Common Dialog APIs *
Type OPENFILENAME
lStructSize As Long
hwndOwner As Long
hInstance As Long
lpstrFilter As String
lpstrCustomFilter As String
nMaxCustFilter As Long
nFilterIndex As Long
lpstrFile As String
nMaxFile As Long
lpstrFileTitle As String
nMaxFileTitle As Long
lpstrInitialDir As String
lpstrTitle As String
flags As Long
nFileOffset As Integer
nFileExtension As Integer
lpstrDefExt As String
lCustData As Long
lpfnHook As Long
lpTemplateName As String
End Type
Declare Function GetOpenFileName Lib "comdlg32.dll" Alias "GetOpenFileNameA" (pOpenfilename As OPENFILENAME) As Long
Declare Function GetSaveFileName Lib "comdlg32.dll" Alias "GetSaveFileNameA" (pOpenfilename As OPENFILENAME) As Long
Declare Function GetFileTitle Lib "comdlg32.dll" Alias "GetFileTitleA" (ByVal lpszFile As String, ByVal lpszTitle As String, ByVal cbBuf As Integer) As Integer
Const OFN_READONLY = &H1
Const OFN_OVERWRITEPROMPT = &H2
Const OFN_HIDEREADONLY = &H4
Const OFN_NOCHANGEDIR = &H8
Const OFN_SHOWHELP = &H10
Const OFN_ENABLEHOOK = &H20
Const OFN_ENABLETEMPLATE = &H40
Const OFN_ENABLETEMPLATEHANDLE = &H80
Const OFN_NOVALIDATE = &H100
Const OFN_ALLOWMULTISELECT = &H200
Const OFN_EXTENSIONDIFFERENT = &H400
Const OFN_PATHMUSTEXIST = &H800
Const OFN_FILEMUSTEXIST = &H1000
Const OFN_CREATEPROMPT = &H2000
Const OFN_SHAREAWARE = &H4000
Const OFN_NOREADONLYRETURN = &H8000
Const OFN_NOTESTFILECREATE = &H10000
Const OFN_NONETWORKBUTTON = &H20000
Const OFN_NOLONGNAMES = &H40000 ' force no long names for 4.x modules
Const OFN_EXPLORER = &H80000 ' new look commdlg
Const OFN_NODEREFERENCELINKS = &H100000
Const OFN_LONGNAMES = &H200000 ' force long names for 3.x modules
Const OFN_SHAREFALLTHROUGH = 2
Const OFN_SHARENOWARN = 1
Const OFN_SHAREWARN = 0
Type NMHDR
hwndFrom As Long
idfrom As Long
code As Long
End Type
Type OFNOTIFY
hdr As NMHDR
lpOFN As OPENFILENAME
pszFile As String ' May be NULL
End Type
Const CDM_FIRST = (WM_USER + 100)
Const CDM_LAST = (WM_USER + 200)
Const CDM_GETSPEC = (CDM_FIRST + &H0)
Const CDM_GETFILEPATH = (CDM_FIRST + &H1)
Const CDM_GETFOLDERPATH = (CDM_FIRST + &H2)
Const CDM_GETFOLDERIDLIST = (CDM_FIRST + &H3)
Const CDM_SETCONTROLTEXT = (CDM_FIRST + &H4)
Const CDM_HIDECONTROL = (CDM_FIRST + &H5)
Const CDM_SETDEFEXT = (CDM_FIRST + &H6)
Type CHOOSECOLOR
lStructSize As Long
hwndOwner As Long
hInstance As Long
rgbResult As Long
lpCustColors As Long
flags As Long
lCustData As Long
lpfnHook As Long
lpTemplateName As String
End Type
Declare Function ChooseColor Lib "comdlg32.dll" Alias "ChooseColorA" (pChoosecolor As CHOOSECOLOR) As Long
Const CC_RGBINIT = &H1
Const CC_FULLOPEN = &H2
Const CC_PREVENTFULLOPEN = &H4
Const CC_SHOWHELP = &H8
Const CC_ENABLEHOOK = &H10
Const CC_ENABLETEMPLATE = &H20
Const CC_ENABLETEMPLATEHANDLE = &H40
Const CC_SOLIDCOLOR = &H80
Const CC_ANYCOLOR = &H100
Type FINDREPLACE
lStructSize As Long ' size of this struct 0x20
hwndOwner As Long ' handle to owner's window
hInstance As Long ' instance handle of.EXE that
' contains cust. dlg. template
flags As Long ' one or more of the FR_??
lpstrFindWhat As String ' ptr. to search string
lpstrReplaceWith As String ' ptr. to replace string
wFindWhatLen As Integer ' size of find buffer
wReplaceWithLen As Integer ' size of replace buffer
lCustData As Long ' data passed to hook fn.
lpfnHook As Long ' ptr. to hook fn. or NULL
lpTemplateName As String ' custom template name
End Type
Const FR_DOWN = &H1
Const FR_WHOLEWORD = &H2
Const FR_MATCHCASE = &H4
Const FR_FINDNEXT = &H8
Const FR_REPLACE = &H10
Const FR_REPLACEALL = &H20
Const FR_DIALOGTERM = &H40
Const FR_SHOWHELP = &H80
Const FR_ENABLEHOOK = &H100
Const FR_ENABLETEMPLATE = &H200
Const FR_NOUPDOWN = &H400
Const FR_NOMATCHCASE = &H800
Const FR_NOWHOLEWORD = &H1000
Const FR_ENABLETEMPLATEHANDLE = &H2000
Const FR_HIDEUPDOWN = &H4000
Const FR_HIDEMATCHCASE = &H8000
Const FR_HIDEWHOLEWORD = &H10000
Declare Function FindText Lib "comdlg32.dll" Alias "FindTextA " (pFindreplace As FINDREPLACE) As Long
Declare Function ReplaceText Lib "comdlg32.dll" Alias "ReplaceTextA" (pFindreplace As FINDREPLACE) As Long
Type CHOOSEFONT
lStructSize As Long
hwndOwner As Long ' caller's window handle
hdc As Long ' printer DC/IC or NULL
lpLogFont As Long
iPointSize As Long ' 10 * size in points of selected font
flags As Long ' enum. type flags
rgbColors As Long ' returned text color
lCustData As Long ' data passed to hook fn.
lpfnHook As Long ' ptr. to hook function
lpTemplateName As String ' custom template name
hInstance As Long ' instance handle of.EXE that
' contains cust. dlg. template
lpszStyle As String ' return the style field here
' must be LF_FACESIZE or bigger
nFontType As Integer ' same value reported to the EnumFonts
' call back with the extra FONTTYPE_
' bits added
MISSING_ALIGNMENT As Integer
nSizeMin As Long ' minimum pt size allowed &
nSizeMax As Long ' max pt size allowed if
' CF_LIMITSIZE is used
End Type
Declare Function ChooseFont Lib "comdlg32.dll" Alias "ChooseFontA" (pChoosefont As CHOOSEFONT) As Long
Const CF_SCREENFONTS = &H1
Const CF_PRINTERFONTS = &H2
Const CF_BOTH = (CF_SCREENFONTS Or CF_PRINTERFONTS)
Const CF_SHOWHELP = &H4&
Const CF_ENABLEHOOK = &H8&
Const CF_ENABLETEMPLATE = &H10&
Const CF_ENABLETEMPLATEHANDLE = &H20&
Const CF_INITTOLOGFONTSTRUCT = &H40&
Const CF_USESTYLE = &H80&
Const CF_EFFECTS = &H100&
Const CF_APPLY = &H200&
Const CF_ANSIONLY = &H400&
Const CF_SCRIPTSONLY = CF_ANSIONLY
Const CF_NOVECTORFONTS = &H800&
Const CF_NOOEMFONTS = CF_NOVECTORFONTS
Const CF_NOSIMULATIONS = &H1000&
Const CF_LIMITSIZE = &H2000&
Const CF_FIXEDPITCHONLY = &H4000&
Const CF_WYSIWYG = &H8000 ' must also have CF_SCREENFONTS CF_PRINTERFONTS
Const PSD_INWININIINTLMEASURE = &H0 ' 1st of 4 possible
Const PSD_MINMARGINS = &H1 ' use caller's
Const PSD_MARGINS = &H2 ' use caller's
Const PSD_INTHOUSANDTHSOFINCHES = &H4 ' 2nd of 4 possible
Const PSD_INHUNDREDTHSOFMILLIMETERS = &H8 ' 3rd of 4 possible
Const PSD_DISABLEMARGINS = &H10
Const PSD_DISABLEPRINTER = &H20
Const PSD_NOWARNING = &H80 ' must be same as PD_*
Const PSD_DISABLEORIENTATION = &H100
Const PSD_RETURNDEFAULT = &H400 ' must be same as PD_*
Const PSD_DISABLEPAPER = &H200
Const PSD_SHOWHELP = &H800 ' must be same as PD_*
Const PSD_ENABLEPAGESETUPHOOK = &H2000 ' must be same as PD_*
Const PSD_ENABLEPAGESETUPTEMPLATE = &H8000 ' must be same as PD_*
Const PSD_ENABLEPAGESETUPTEMPLATEHANDLE = &H20000 ' must be same as PD_*
Const PSD_ENABLEPAGEPAINTHOOK = &H40000
Const PSD_DISABLEPAGEPAINTING = &H80000
Declare Function DdeInitialize Lib "user32" Alias "DdeInitializeA" (pidInst As Long, ByVal pfnCallback As Long, ByVal afCmd As Long, ByVal ulRes As Long) As Integer
Declare Function SetServiceBits Lib "advapi32" Alias "SetServiceBits" (ByVal hServiceStatus As Long, ByVal dwServiceBits As Long, ByVal bSetBitsOn As Boolean, ByVal bUpdateImmediately As Boolean) As Long
Declare Function CopyLZFile Lib "lz32" Alias "CopyLZFile" (ByVal n1 As Long, ByVal n2 As Long) As Long
Declare Function LZStart Lib "lz32" Alias "LZStart" () As Long
Declare Sub LZDone Lib "lz32" Alias "LZDone" ()
Declare Function mciGetYieldProc Lib "winmm" Alias "mciGetYieldProc" (ByVal mciId As Long, pdwYieldData As Long) As Long
Declare Function mciSetYieldProc Lib "winmm" Alias "mciSetYieldProc" (ByVal mciId As Long, ByVal fpYieldProc As Long, ByVal dwYieldData As Long) As Long
Declare Function midiOutGetNumDevs Lib "winmm" Alias "midiOutGetNumDevs" () As Integer
Declare Function mmioInstallIOProcA Lib "winmm" Alias "mmioInstallIOProcA" (ByVal fccIOProc As String * 4, ByVal pIOProc As Long, ByVal dwFlags As Long) As Long
Declare Function CommandLineToArgv Lib "shell32" Alias "CommandLineToArgvW" (ByVal lpCmdLine As String, pNumArgs As Integer) As Long
Declare Function IsTextUnicode Lib "advapi32" Alias "IsTextUnicode" (lpBuffer As Any, ByVal cb As Long, lpi As Long) As Long
Declare Function NotifyChangeEventLog Lib "advapi32" Alias "NotifyChangeEventLog" (ByVal hEventLog As Long, ByVal hEvent As Long) As Long
Declare Function SetThreadToken Lib "advapi32" Alias "SetThreadToken" (Thread As Long, ByVal Token As Long) As Long
Type COMMCONFIG
dwSize As Long
wVersion As Integer
wReserved As Integer
dcbx As DCB
dwProviderSubType As Long
dwProviderOffset As Long
dwProviderSize As Long
wcProviderData As Byte
End Type
Declare Function CommConfigDialog Lib "kernel32" Alias "CommConfigDialogA" (ByVal lpszName As String, ByVal hWnd As Long, lpCC As COMMCONFIG) As Long
Declare Function CreateIoCompletionPort Lib "kernel32" Alias "CreateIoCompletionPort" (ByVal FileHandle As Long, ByVal ExistingCompletionPort As Long, ByVal CompletionKey As Long, ByVal NumberOfConcurrentThreads As Long) As Long
Declare Function DisableThreadLibraryCalls Lib "kernel32" Alias "DisableThreadLibraryCalls" (ByVal hLibModule As Long) As Long
Declare Function EnumResourceLanguages Lib "kernel32" Alias "EnumResourceLanguagesA" (ByVal hModule As Long, ByVal lpType As String, ByVal lpName As String, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function EnumResourceNames Lib "kernel32" Alias "EnumResourceNamesA" (ByVal hModule As Long, ByVal lpType As String, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function EnumResourceTypes Lib "kernel32" Alias "EnumResourceTypesA" (ByVal hModule As Long, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function FreeEnvironmentStrings Lib "kernel32" Alias "FreeEnvironmentStringsA" (ByVal lpsz As String) As Long
Declare Sub FreeLibraryAndExitThread Lib "kernel32" Alias "FreeLibraryAndExitThread" (ByVal hLibModule As Long, ByVal dwExitCode As Long)
Declare Function FreeResource Lib "kernel32" Alias "FreeResource" (ByVal hResData As Long) As Long
Declare Function GetCommConfig Lib "kernel32" Alias "GetCommConfig" (ByVal hCommDev As Long, lpCC As COMMCONFIG, lpdwSize As Long) As Long
Declare Function GetCompressedFileSize Lib "kernel32" Alias "GetCompressedFileSizeA" (ByVal lpFileName As String, lpFileSizeHigh As Long) As Long
Declare Function GetDefaultCommConfig Lib "kernel32" Alias "GetDefaultCommConfigA" (ByVal lpszName As String, lpCC As COMMCONFIG, lpdwSize As Long) As Long
Declare Function GetHandleInformation Lib "kernel32" Alias "GetHandleInformation" (ByVal hObject As Long, lpdwFlags As Long) As Long
Declare Function GetProcessHeaps Lib "kernel32" Alias "GetProcessHeaps" (ByVal NumberOfHeaps As Long, ProcessHeaps As Long) As Long
Declare Function GetProcessWorkingSetSize Lib "kernel32" Alias "GetProcessWorkingSetSize" (ByVal hProcess As Long, lpMinimumWorkingSetSize As Long, lpMaximumWorkingSetSize As Long) As Long
Declare Function GetQueuedCompletionStatus Lib "kernel32" Alias "GetQueuedCompletionStatus" (ByVal CompletionPort As Long, lpNumberOfBytesTransferred As Long, lpCompletionKey As Long, lpOverlapped As Long, ByVal dwMilliseconds As Long) As Long
Declare Function GetSystemTimeAdjustment Lib "kernel32" Alias "GetSystemTimeAdjustment" (lpTimeAdjustment As Long, lpTimeIncrement As Long, lpTimeAdjustmentDisabled As Long) As Long
Declare Function GlobalCompact Lib "kernel32" Alias "GlobalCompact" (ByVal dwMinFree As Long) As Long
Declare Sub GlobalFix Lib "kernel32" Alias "GlobalFix" (ByVal hMem As Long)
Declare Sub GlobalUnfix Lib "kernel32" Alias "GlobalUnfix" (ByVal hMem As Long)
Declare Function GlobalWire Lib "kernel32" Alias "GlobalWire" (ByVal hMem As Long) As Long
Declare Function GlobalUnWire Lib "kernel32" Alias "GlobalUnWire" (ByVal hMem As Long) As Long
Declare Function IsBadCodePtr Lib "kernel32" Alias "IsBadCodePtr" (ByVal lpfn As Long) As Long
Declare Function LocalCompact Lib "kernel32" Alias "LocalCompact" (ByVal uMinFree As Long) As Long
Declare Function LocalShrink Lib "kernel32" Alias "LocalShrink" (ByVal hMem As Long, ByVal cbNewSize As Long) As Long
Declare Sub ZeroMemory Lib "KERNEL32" Alias "RtlMoveMemory" (dest As Any, ByVal numBytes As Long)
Declare Function ReadFileEx Lib "kernel32" Alias "ReadFileEx" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpOverlapped As OVERLAPPED, ByVal lpCompletionRoutine As Long) As Long
Declare Function SetCommConfig Lib "kernel32" Alias "SetCommConfig" (ByVal hCommDev As Long, lpCC As COMMCONFIG, ByVal dwSize As Long) As Long
Declare Function SetDefaultCommConfig Lib "kernel32" Alias "SetDefaultCommConfigA" (ByVal lpszName As String, lpCC As COMMCONFIG, ByVal dwSize As Long) As Long
Declare Sub SetFileApisToANSI Lib "kernel32" Alias "SetFileApisToANSI" ()
Declare Function SetHandleInformation Lib "kernel32" Alias "SetHandleInformation" (ByVal hObject As Long, ByVal dwMask As Long, ByVal dwFlags As Long) As Long
Declare Function SetProcessWorkingSetSize Lib "kernel32" Alias "SetProcessWorkingSetSize" (ByVal hProcess As Long, ByVal dwMinimumWorkingSetSize As Long, ByVal dwMaximumWorkingSetSize As Long) As Long
Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long
Declare Function lstrcpyn Lib "kernel32" Alias "lstrcpynA" (ByVal lpString1 As String, ByVal lpString2 As String, ByVal iMaxLength As Long) As Long
Declare Function lstrcpy Lib "kernel32" Alias "lstrcpyA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long
Declare Function SetSystemTimeAdjustment Lib "kernel32" Alias "SetSystemTimeAdjustment" (ByVal dwTimeAdjustment As Long, ByVal bTimeAdjustmentDisabled As Boolean) As Long
Declare Function SetThreadAffinityMask Lib "kernel32" Alias "SetThreadAffinityMask" (ByVal hThread As Long, ByVal dwThreadAffinityMask As Long) As Long
Declare Function SetUnhandledExceptionFilter Lib "kernel32" Alias "SetUnhandledExceptionFilter" (ByVal lpTopLevelExceptionFilter As Long) As Long
Declare Function SystemTimeToTzSpecificLocalTime Lib "kernel32" Alias "SystemTimeToTzSpecificLocalTime" (lpTimeZoneInformation As TIME_ZONE_INFORMATION, lpUniversalTime As SYSTEMTIME, lpLocalTime As SYSTEMTIME) As Long
Declare Function WriteFileEx Lib "kernel32" Alias "WriteFileEx" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpOverlapped As OVERLAPPED, ByVal lpCompletionRoutine As Long) As Long
Type PIXELFORMATDESCRIPTOR
nSize As Integer
nVersion As Integer
dwFlags As Long
iPixelType As Byte
cColorBits As Byte
cRedBits As Byte
cRedShift As Byte
cGreenBits As Byte
cGreenShift As Byte
cBlueBits As Byte
cBlueShift As Byte
cAlphaBits As Byte
cAlphaShift As Byte
cAccumBits As Byte
cAccumRedBits As Byte
cAccumGreenBits As Byte
cAccumBlueBits As Byte
cAccumAlphaBits As Byte
cDepthBits As Byte
cStencilBits As Byte
cAuxBuffers As Byte
iLayerType As Byte
bReserved As Byte
dwLayerMask As Long
dwVisibleMask As Long
dwDamageMask As Long
End Type
Declare Function ChoosePixelFormat Lib "gdi32" Alias "ChoosePixelFormat" (ByVal hDC As Long, pPixelFormatDescriptor As PIXELFORMATDESCRIPTOR) As Long
Declare Function CreateDIBSection Lib "gdi32" Alias "CreateDIBSection" (ByVal hDC As Long, pBitmapInfo As BITMAPINFO, ByVal un As Long, ByVal lplpVoid As Long, ByVal handle As Long, ByVal dw As Long) As Long
Declare Function DescribePixelFormat Lib "gdi32" Alias "DescribePixelFormat" (ByVal hDC As Long, ByVal n As Long, ByVal un As Long, lpPixelFormatDescriptor As PIXELFORMATDESCRIPTOR) As Long
Declare Function EndDoc Lib "gdi32" Alias "EndDoc" (ByVal hDC As Long) As Long
Declare Function EnumFonts Lib "gdi32" Alias "EnumFontsA" (ByVal hDC As Long, ByVal lpsz As String, ByVal lpFontEnumProc As Long, ByVal lParam As Long) As Long
Declare Function EnumMetaFile Lib "gdi32" Alias "EnumMetaFile" (ByVal hDC As Long, ByVal hMetafile As Long, ByVal lpMFEnumProc As Long, ByVal lParam As Long) As Long
Declare Function EnumObjects Lib "gdi32" Alias "EnumObjects" (ByVal hDC As Long, ByVal n As Long, ByVal lpGOBJEnumProc As Long, lpVoid As Any) As Long
Declare Function FixBrushOrgEx Lib "gdi32" Alias "FixBrushOrgEx" (ByVal hDC As Long, ByVal n1 As Long, ByVal n2 As Long, lpPoint As POINTAPI) As Long
Declare Function GetBrushOrgEx Lib "gdi32" Alias "GetBrushOrgEx" (ByVal hDC As Long, lpPoint As POINTAPI) As Long
Declare Function GetDIBColorTable Lib "gdi32" Alias "GetDIBColorTable" (ByVal hDC As Long, ByVal un1 As Long, ByVal un2 As Long, pRGBQuad As RGBQUAD) As Long
Declare Function GetPixelFormat Lib "gdi32" Alias "GetPixelFormat" (ByVal hDC As Long) As Long
Declare Function LineDDA Lib "gdi32" Alias "LineDDA" (ByVal n1 As Long, ByVal n2 As Long, ByVal n3 As Long, ByVal n4 As Long, ByVal lpLineDDAProc As Long, ByVal lParam As Long) As Long
Declare Function SetAbortProc Lib "gdi32" Alias "SetAbortProc" (ByVal hDC As Long, ByVal lpAbortProc As Long) As Long
Declare Function SetDIBColorTable Lib "gdi32" Alias "SetDIBColorTable" (ByVal hDC As Long, ByVal un1 As Long, ByVal un2 As Long, pcRGBQuad As RGBQUAD) As Long
Declare Function SetPixelFormat Lib "gdi32" Alias "SetPixelFormat" (ByVal hDC As Long, ByVal n As Long, pcPixelFormatDescriptor As PIXELFORMATDESCRIPTOR) As Long
Declare Function SwapBuffers Lib "gdi32" Alias "SwapBuffers" (ByVal hDC As Long) As Long
Declare Function EnumCalendarInfo Lib "kernel32" Alias "EnumCalendarInfoA" (ByVal lpCalInfoEnumProc As Long, ByVal Locale As Long, ByVal Calendar As Long, ByVal CalType As Long) As Long
Declare Function GetCurrencyFormat Lib "kernel32" Alias "GetCurrencyFormatA" (ByVal Locale As Long, ByVal dwFlags As Long, ByVal lpValue As String, lpFormat As CURRENCYFMT, ByVal lpCurrencyStr As String, ByVal cchCurrency As Long) As Long
Declare Function GetNumberFormat Lib "kernel32" Alias "GetNumberFormatA" (ByVal Locale As Long, ByVal dwFlags As Long, ByVal lpValue As String, lpFormat As NUMBERFMT, ByVal lpNumberStr As String, ByVal cchNumber As Long) As Long
Declare Function GetStringTypeEx Lib "kernel32" Alias "GetStringTypeExA" (ByVal Locale As Long, ByVal dwInfoType As Long, ByVal lpSrcStr As String, ByVal cchSrc As Long, lpCharType As Integer) As Long
Declare Function GetStringTypeW Lib "kernel32" Alias "GetStringTypeW" (ByVal dwInfoType As Long, ByVal lpSrcStr As String, ByVal cchSrc As Long, lpCharType As Integer) As Long
Declare Function SetLocaleInfo Lib "kernel32" Alias "SetLocaleInfoA" (ByVal Locale As Long, ByVal LCType As Long, ByVal lpLCData As String) As Long
Declare Function DeletePrinter Lib "winspool.drv" Alias "DeletePrinter" (ByVal hPrinter As Long) As Long
Declare Function FindClosePrinterChangeNotification Lib "winspool.drv" Alias "FindClosePrinterChangeNotification" (ByVal hChange As Long) As Long
Declare Function FindFirstPrinterChangeNotification Lib "winspool.drv" Alias "FindFirstPrinterChangeNotification" (ByVal hPrinter As Long, ByVal fdwFlags As Long, ByVal fdwOptions As Long, ByVal pPrinterNotifyOptions As String) As Long
Declare Function FindNextPrinterChangeNotification Lib "winspool.drv" Alias "FindNextPrinterChangeNotification" (ByVal hChange As Long, pdwChange As Long, ByVal pvReserved As String, ByVal ppPrinterNotifyInfo As Long) As Long
Declare Function GetPrinter Lib "winspool.drv" Alias "GetPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, pPrinter As Any, ByVal cbBuf As Long, pcbNeeded As Long) As Long
Declare Function SetPrinter Lib "winspool.drv" Alias "SetPrinterA" (ByVal hPrinter As Long, ByVal Level As Long, pPrinter As Byte, ByVal Command As Long) As Long
Declare Function BroadcastSystemMessage Lib "user32" Alias "BroadcastSystemMessage" (ByVal dw As Long, pdw As Long, ByVal un As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hWnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Declare Function CascadeWindows Lib "user32" Alias "CascadeWindows" (ByVal hwndParent As Long, ByVal wHow As Long, ByVal lpRect As RECT, ByVal cKids As Long, lpkids As Long) As Integer
Declare Function ChangeMenu Lib "user32" Alias "ChangeMenuA" (ByVal hMenu As Long, ByVal cmd As Long, ByVal lpszNewItem As String, ByVal cmdInsert As Long, ByVal flags As Long) As Long
Declare Function CheckMenuRadioItem Lib "user32" Alias "CheckMenuRadioItem" (ByVal hMenu As Long, ByVal un1 As Long, ByVal un2 As Long, ByVal un3 As Long, ByVal un4 As Long) As Long
Declare Function ChildWindowFromPoint Lib "user32" Alias "ChildWindowFromPoint" (ByVal hWndParent As Long, ByVal pt As POINTAPI) As Long
Declare Function ChildWindowFromPointEx Lib "user32" Alias "ChildWindowFromPointEx" (ByVal hWnd As Long, ByVal pt As POINTAPI, ByVal un As Long) As Long
Declare Function CloseDesktop Lib "user32" Alias "CloseDesktop" (ByVal hDesktop As Long) As Long
Declare Function CloseWindowStation Lib "user32" Alias "CloseWindowStation" (ByVal hWinSta As Long) As Long
Declare Function CopyImage Lib "user32" Alias "CopyImage" (ByVal handle As Long, ByVal un1 As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal un2 As Long) As Long
Declare Function CreateDesktop Lib "user32" Alias "CreateDesktopA" (ByVal lpszDesktop As String, ByVal lpszDevice As String, pDevmode As DEVMODE, ByVal dwFlags As Long, ByVal dwDesiredAccess As Long, lpsa As SECURITY_ATTRIBUTES) As Long
Declare Function CreateDialogIndirectParam Lib "user32" Alias "CreateDialogIndirectParamA" (ByVal hInstance As Long, lpTemplate As DLGTEMPLATE, ByVal hWndParent As Long, ByVal lpDialogFunc As Long, ByVal dwInitParam As Long) As Long
Declare Function CreateDialogParam Lib "user32" Alias "CreateDialogParamA" (ByVal hInstance As Long, ByVal lpName As String, ByVal hWndParent As Long, ByVal lpDialogFunc As Long, ByVal lParamInit As Long) As Long
Declare Function CreateIconFromResource Lib "user32" Alias "CreateIconFromResource" (presbits As Byte, ByVal dwResSize As Long, ByVal fIcon As Long, ByVal dwVer As Long) As Long
Declare Function DialogBoxIndirectParam Lib "user32" Alias "DialogBoxIndirectParamA" (ByVal hInstance As Long, hDialogTemplate As DLGTEMPLATE, ByVal hWndParent As Long, ByVal lpDialogFunc As Long, ByVal dwInitParam As Long) As Long
Declare Function DragDetect Lib "user32" Alias "DragDetect" (ByVal hWnd As Long, ByVal pt As POINTAPI) As Long
Declare Function DragObject Lib "user32" Alias "DragObject" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal un As Long, ByVal dw As Long, ByVal hCursor As Long) As Long
Declare Function DrawAnimatedRects Lib "user32" Alias "DrawAnimatedRects" (ByVal hwnd As Long, ByVal idAni As Long, lprcFrom As Rect, lprcTo As Rect) As Long
Declare Function DrawCaption Lib "user32" Alias "DrawCaption" (ByVal hWnd As Long, ByVal hDC As Long, pcRect As Rect, ByVal un As Long) As Long
Declare Function DrawEdge Lib "user32" Alias "DrawEdge" (ByVal hdc As Long, qrc As RECT, ByVal edge As Long, ByVal grfFlags As Long) As Long
Declare Function DrawFrameControl Lib "user32" Alias "DrawFrameControl" (ByVal hDC As Long, lpRect As RECT, ByVal un1 As Long, ByVal un2 As Long) As Long
Declare Function DrawIconEx Lib "user32" Alias "DrawIconEx" (ByVal hdc As Long, ByVal xLeft As Long, ByVal yTop As Long, ByVal hIcon As Long, ByVal cxWidth As Long, ByVal cyWidth As Long, ByVal istepIfAniCur As Long, ByVal hbrFlickerFreeDraw As Long, ByVal diFlags As Long) As Long
Declare Function DrawState Lib "user32" Alias "DrawStateA" (ByVal hDC As Long, ByVal hBrush As Long, ByVal lpDrawStateProc As Long, ByVal lParam As Long, ByVal wParam As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal n3 As Long, ByVal n4 As Long, ByVal un As Long) As Long
Type DRAWTEXTPARAMS
cbSize As Long
iTabLength As Long
iLeftMargin As Long
iRightMargin As Long
uiLengthDrawn As Long
End Type
Declare Function DrawTextEx Lib "user32" Alias "DrawTextExA" (ByVal hDC As Long, ByVal lpsz As String, ByVal n As Long, lpRect As RECT, ByVal un As Long, lpDrawTextParams As DRAWTEXTPARAMS) As Long
Declare Function EnumChildWindows Lib "user32" Alias "EnumChildWindows" (ByVal hWndParent As Long, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function EnumDesktops Lib "user32" Alias "EnumDesktopsA" (ByVal hwinsta As Long, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function EnumDesktopWindows Lib "user32" Alias "EnumDesktopWindows" (ByVal hDesktop As Long, ByVal lpfn As Long, ByVal lParam As Long) As Long
Declare Function EnumPropsEx Lib "user32" Alias "EnumPropsExA" (ByVal hWnd As Long, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function EnumProps Lib "user32" Alias "EnumPropsA" (ByVal hWnd As Long, ByVal lpEnumFunc As Long) As Long
Declare Function EnumThreadWindows Lib "user32" Alias "EnumThreadWindows" (ByVal dwThreadId As Long, ByVal lpfn As Long, ByVal lParam As Long) As Long
Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function EnumWindowStations Lib "user32" Alias "EnumWindowStationsA" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
Declare Function GetKeyboardLayoutList Lib "user32" Alias "GetKeyboardLayoutList" (ByVal nBuff As Long, lpList As Long) As Long
Declare Function GetKeyboardLayout Lib "user32" Alias "GetKeyboardLayout" (ByVal dwLayout As Long) As Long
Declare Function GetMenuContextHelpId Lib "user32" Alias "GetMenuContextHelpId" (ByVal hMenu As Long) As Long
Declare Function GetMenuDefaultItem Lib "user32" Alias "GetMenuDefaultItem" (ByVal hMenu As Long, ByVal fByPos As Long, ByVal gmdiFlags As Long) As Long
Type MENUITEMINFO
cbSize As Long
fMask As Long
fType As Long
fState As Long
wID As Long
hSubMenu As Long
hbmpChecked As Long
hbmpUnchecked As Long
dwItemData As Long
dwTypeData As String
cch As Long
End Type
Declare Function GetMenuItemInfo Lib "user32" Alias "GetMenuItemInfoA" (ByVal hMenu As Long, ByVal un As Long, ByVal b As Long, lpMenuItemInfo As MENUITEMINFO) As Long
Declare Function GetMenuItemRect Lib "user32" Alias "GetMenuItemRect" (ByVal hWnd As Long, ByVal hMenu As Long, ByVal uItem As Long, lprcItem As RECT) As Long
Type SCROLLINFO
cbSize As Long
fMask As Long
nMin As Long
nMax As Long
nPage As Long
nPos As Long
nTrackPos As Long
End Type
Declare Function GetScrollInfo Lib "user32" Alias "GetScrollInfo" (ByVal hWnd As Long, ByVal n As Long, lpScrollInfo As SCROLLINFO) As Long
Declare Function GetSysColorBrush Lib "user32" Alias "GetSysColorBrush" (ByVal nIndex As Long) As Long
Declare Function GetUserObjectInformation Lib "user32" Alias "GetUserObjectInformationA" (ByVal hObj As Long, ByVal nIndex As Long, pvInfo As Any, ByVal nLength As Long, lpnLengthNeeded As Long) As Long
Declare Function GetWindowContextHelpId Lib "user32" Alias "GetWindowContextHelpId" (ByVal hWnd As Long) As Long
Declare Function GetWindowRgn Lib "user32" Alias "GetWindowRgn" (ByVal hWnd As Long, ByVal hRgn As Long) As Long
Declare Function GrayString Lib "user32" Alias "GrayStringA" (ByVal hDC As Long, ByVal hBrush As Long, ByVal lpOutputFunc As Long, ByVal lpData As Long, ByVal nCount As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Declare Function InsertMenuItem Lib "user32" Alias "InsertMenuItemA" (ByVal hMenu As Long, ByVal un As Long, ByVal bool As Boolean, ByRef lpcMenuItemInfo As MENUITEMINFO) As Long
Declare Function LoadCursorFromFile Lib "user32" Alias "LoadCursorFromFileA" (ByVal lpFileName As String) As Long
Declare Function LoadImage Lib "user32" Alias "LoadImageA" (ByVal hInst As Long, ByVal lpsz As String, ByVal un1 As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal un2 As Long) As Long
Declare Function LookupIconIdFromDirectoryEx Lib "user32" Alias "LookupIconIdFromDirectoryEx" (presbits As Byte, ByVal fIcon As Boolean, ByVal cxDesired As Long, ByVal cyDesired As Long, ByVal Flags As Long) As Long
Declare Function MapVirtualKeyEx Lib "user32" Alias "MapVirtualKeyExA" (ByVal uCode As Long, ByVal uMapType As Long, ByVal dwhkl As Long) As Long
Declare Function MenuItemFromPoint Lib "user32" Alias "MenuItemFromPoint" (ByVal hWnd As Long, ByVal hMenu As Long, ByVal ptScreen As POINTAPI) As Long
Type MSGBOXPARAMS
cbSize As Long
hwndOwner As Long
hInstance As Long
lpszText As String
lpszCaption As String
dwStyle As Long
lpszIcon As String
dwContextHelpId As Long
lpfnMsgBoxCallback As Long
dwLanguageId As Long
End Type
Declare Function MessageBoxIndirect Lib "user32" Alias "MessageBoxIndirectA" (lpMsgBoxParams As MSGBOXPARAMS) As Long
Declare Function OpenDesktop Lib "user32" Alias "OpenDesktopA" (ByVal lpszDesktop As String, ByVal dwFlags As Long, ByVal fInherit As Boolean, ByVal dwDesiredAccess As Long) As Long
Declare Function OpenInputDesktop Lib "user32" Alias "OpenInputDesktop" (ByVal dwFlags As Long, ByVal fInherit As Boolean, ByVal dwDesiredAccess As Long) As Long
Declare Function OpenWindowStation Lib "user32" Alias "OpenWindowStationA" (ByVal lpszWinSta As String, ByVal fInherit As Boolean, ByVal dwDesiredAccess As Long) As Long
Declare Function PaintDesktop Lib "user32" Alias "PaintDesktop" (ByVal hdc As Long) As Long
Type WNDCLASSEX
cbSize As Long
style As Long
lpfnWndProc As Long
cbClsExtra As Long
cbWndExtra As Long
hInstance As Long
hIcon As Long
hCursor As Long
hbrBackground As Long
lpszMenuName As String
lpszClassName As String
hIconSm As Long
End Type
Declare Function RegisterClassEx Lib "user32" Alias "RegisterClassExA" (pcWndClassEx As WNDCLASSEX) As Integer
Declare Function SetMenuContextHelpId Lib "user32" Alias "SetMenuContextHelpId" (ByVal hMenu As Long, ByVal dw As Long) As Long
Declare Function SetMenuDefaultItem Lib "user32" Alias "SetMenuDefaultItem" (ByVal hMenu As Long, ByVal uItem As Long, ByVal fByPos As Long) As Long
Declare Function SetMenuItemInfo Lib "user32" Alias "SetMenuItemInfoA" (ByVal hMenu As Long, ByVal un As Long, ByVal bool As Boolean, lpcMenuItemInfo As MENUITEMINFO) As Long
Declare Function SetMessageExtraInfo Lib "user32" Alias "SetMessageExtraInfo" (ByVal lParam As Long) As Long
Declare Function SetMessageQueue Lib "user32" Alias "SetMessageQueue" (ByVal cMessagesMax As Long) As Long
Declare Function SetProcessWindowStation Lib "user32" Alias "SetProcessWindowStation" (ByVal hWinSta As Long) As Long
Declare Function SetScrollInfo Lib "user32" Alias "SetScrollInfo" (ByVal hWnd As Long, ByVal n As Long, lpcScrollInfo As SCROLLINFO, ByVal bool As Boolean) As Long
Declare Function SetSystemCursor Lib "user32" Alias "SetSystemCursor" (ByVal hcur As Long, ByVal id As Long) As Long
Declare Function SetThreadDesktop Lib "user32" Alias "SetThreadDesktop" (ByVal hDesktop As Long) As Long
Declare Function SetTimer Lib "user32" Alias "SetTimer" (ByVal hWnd As Long, ByVal nIDEvent As Long, ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
Declare Function SetUserObjectInformation Lib "user32" Alias "SetUserObjectInformationA" (ByVal hObj As Long, ByVal nIndex As Long, pvInfo As Any, ByVal nLength As Long) As Long
Declare Function SetWindowContextHelpId Lib "user32" Alias "SetWindowContextHelpId" (ByVal hWnd As Long, ByVal dw As Long) As Long
Declare Function SetWindowRgn Lib "user32" Alias "SetWindowRgn" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Boolean) As Long
Declare Function SetWindowsHook Lib "user32" Alias "SetWindowsHookA" (ByVal nFilterType As Long, ByVal pfnFilterProc As Long) As Long
Declare Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" (ByVal idHook As Long, ByVal lpfn As Long, ByVal hmod As Long, ByVal dwThreadId As Long) As Long
Declare Function ShowWindowAsync Lib "user32" Alias "ShowWindowAsync" (ByVal hWnd As Long, ByVal nCmdShow As Long) As Long
Declare Function SwitchDesktop Lib "user32" Alias "SwitchDesktop" (ByVal hDesktop As Long) As Long
Declare Function TileWindows Lib "user32" Alias "TileWindows" (ByVal hwndParent As Long, ByVal wHow As Long, lpRect As Rect, ByVal cKids As Long, lpKids As Long) As Integer
Declare Function ToAsciiEx Lib "user32" Alias "ToAsciiEx" (ByVal uVirtKey As Long, ByVal uScanCode As Long, lpKeyState As Byte, lpChar As Integer, ByVal uFlags As Long, ByVal dwhkl As Long) As Long
Type TPMPARAMS
cbSize As Long
rcExclude As Rect
End Type
Declare Function TrackPopupMenuEx Lib "user32" Alias "TrackPopupMenuEx" (ByVal hMenu As Long, ByVal un As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal hWnd As Long, lpTPMParams As TPMPARAMS) As Long
Declare Function UnhookWindowsHook Lib "user32" Alias "UnhookWindowsHook" (ByVal nCode As Long, ByVal pfnFilterProc As Long) As Long
Declare Function VkKeyScanEx Lib "user32" Alias "VkKeyScanExA" (ByVal ch As Byte, ByVal dwhkl As Long) As Integer
Declare Function WNetGetUniversalName Lib "mpr" Alias "WNetGetUniversalNameA" (ByVal lpLocalPath As String, ByVal dwInfoLevel As Long, lpBuffer As Any, lpBufferSize As Long) As Long
Const INVALID_HANDLE_VALUE = -1
'DrawEdge Constants
Const BDR_RAISEDOUTER = &H1
Const BDR_SUNKENOUTER = &H2
Const BDR_RAISEDINNER = &H4
Const BDR_SUNKENINNER = &H8
Const BDR_OUTER = &H3
Const BDR_INNER = &HC
Const BDR_RAISED = &H5
Const BDR_SUNKEN = &HA
Const EDGE_RAISED = (BDR_RAISEDOUTER Or BDR_RAISEDINNER)
Const EDGE_SUNKEN = (BDR_SUNKENOUTER Or BDR_SUNKENINNER)
Const EDGE_ETCHED = (BDR_SUNKENOUTER Or BDR_RAISEDINNER)
Const EDGE_BUMP = (BDR_RAISEDOUTER Or BDR_SUNKENINNER)
Const BF_LEFT = &H1
Const BF_TOP = &H2
Const BF_RIGHT = &H4
Const BF_BOTTOM = &H8
Const BF_TOPLEFT = (BF_TOP Or BF_LEFT)
Const BF_TOPRIGHT = (BF_TOP Or BF_RIGHT)
Const BF_BOTTOMLEFT = (BF_BOTTOM Or BF_LEFT)
Const BF_BOTTOMRIGHT = (BF_BOTTOM Or BF_RIGHT)
Const BF_RECT = (BF_LEFT Or BF_TOP Or BF_RIGHT Or BF_BOTTOM)
Const BF_DIAGONAL = &H10
' For diagonal lines, the BF_RECT flags specify the end point of
' the vector bounded by the rectangle parameter.
Const BF_DIAGONAL_ENDTOPRIGHT = (BF_DIAGONAL Or BF_TOP Or BF_RIGHT)
Const BF_DIAGONAL_ENDTOPLEFT = (BF_DIAGONAL Or BF_TOP Or BF_LEFT)
Const BF_DIAGONAL_ENDBOTTOMLEFT = (BF_DIAGONAL Or BF_BOTTOM Or BF_LEFT)
Const BF_DIAGONAL_ENDBOTTOMRIGHT = (BF_DIAGONAL Or BF_BOTTOM Or BF_RIGHT)
Const BF_MIDDLE = &H800 ' Fill in the middle.
Const BF_SOFT = &H1000 ' Use for softer buttons.
Const BF_ADJUST = &H2000 ' Calculate the space left over.
Const BF_FLAT = &H4000 ' For flat rather than 3-D borders.